{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 701
{-# LANGUAGE Trustworthy #-}
#endif
--
-- |
-- Module      :  Data.ByteString.UTF8
-- Copyright   :  (c) Iavor S. Diatchki 2009
-- License     :  BSD3-style (see LICENSE)
--
-- Maintainer  :  emertens@galois.com
-- Stability   :  experimental
-- Portability :  portable
--
--   This module provides fast, validated encoding and decoding functions
--   between 'ByteString's and 'String's. It does not exactly match the
--   output of the Codec.Binary.UTF8.String output for invalid encodings
--   as the number of replacement characters is sometimes longer.
module Data.ByteString.UTF8
  ( B.ByteString
  , decode
  , replacement_char
  , uncons
  , splitAt
  , take
  , drop
  , span
  , break
  , fromChar
  , fromString
  , toString
  , foldl
  , foldr
  , length
  , lines
  , lines'
  ) where

import Data.Bits
import Data.Word
import qualified Data.ByteString as B
import Prelude hiding (take,drop,splitAt,span,break,foldr,foldl,length,lines)

import Codec.Binary.UTF8.String(encode)
import Codec.Binary.UTF8.Generic (buncons)

-- | Converts a Haskell char into a UTF8 encoded bytestring.
fromChar :: Char -> B.ByteString
fromChar :: Char -> ByteString
fromChar Char
x = String -> ByteString
fromString [Char
x]

-- | Converts a Haskell string into a UTF8 encoded bytestring.
fromString :: String -> B.ByteString
fromString :: String -> ByteString
fromString String
xs = [Word8] -> ByteString
B.pack (String -> [Word8]
encode String
xs)

-- | Convert a UTF8 encoded bytestring into a Haskell string.
-- Invalid characters are replaced with @\'\\0xFFFD\'@.
toString :: B.ByteString -> String
toString :: ByteString -> String
toString ByteString
bs = (Char -> String -> String) -> String -> ByteString -> String
forall a. (Char -> a -> a) -> a -> ByteString -> a
foldr (:) [] ByteString
bs

-- | This character is used to mark errors in a UTF8 encoded string.
replacement_char :: Char
replacement_char :: Char
replacement_char = Char
'\xfffd'

-- | Try to extract a character from a byte string.
-- Returns 'Nothing' if there are no more bytes in the byte string.
-- Otherwise, it returns a decoded character and the number of
-- bytes used in its representation.
-- Errors are replaced by character @\'\\0xFFFD\'@.

-- XXX: Should we combine sequences of errors into a single replacement
-- character?
decode :: B.ByteString -> Maybe (Char,Int)
decode :: ByteString -> Maybe (Char, Int)
decode ByteString
bs = do (Word8
c,ByteString
cs) <- ByteString -> Maybe (Word8, ByteString)
forall b s. UTF8Bytes b s => b -> Maybe (Word8, b)
buncons ByteString
bs
               (Char, Int) -> Maybe (Char, Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> ByteString -> (Char, Int)
choose (Word8 -> Int
forall a. Enum a => a -> Int
fromEnum Word8
c) ByteString
cs)
  where
  choose :: Int -> B.ByteString -> (Char, Int)
  choose :: Int -> ByteString -> (Char, Int)
choose Int
c ByteString
cs
    | Int
c Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0x80  = (Int -> Char
forall a. Enum a => Int -> a
toEnum (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$ Int -> Int
forall a. Enum a => a -> Int
fromEnum Int
c, Int
1)
    | Int
c Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0xc0  = (Char
replacement_char, Int
1)
    | Int
c Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0xe0  = Int -> ByteString -> (Char, Int)
bytes2 (Int -> Int -> Int
mask Int
c Int
0x1f) ByteString
cs
    | Int
c Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0xf0  = Int -> ByteString -> (Char, Int)
bytes3 (Int -> Int -> Int
mask Int
c Int
0x0f) ByteString
cs
    | Int
c Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0xf8  = Int -> ByteString -> (Char, Int)
bytes4 (Int -> Int -> Int
mask Int
c Int
0x07) ByteString
cs
    | Bool
otherwise = (Char
replacement_char, Int
1)

  mask :: Int -> Int -> Int
  mask :: Int -> Int -> Int
mask Int
c Int
m = Int -> Int
forall a. Enum a => a -> Int
fromEnum (Int
c Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
m)

  combine :: Int -> Word8 -> Int
  combine :: Int -> Word8 -> Int
combine Int
acc Word8
r = Int -> Int -> Int
forall a. Bits a => a -> Int -> a
shiftL Int
acc Int
6 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.|. Word8 -> Int
forall a. Enum a => a -> Int
fromEnum (Word8
r Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x3f)

  follower :: Int -> Word8 -> Maybe Int
  follower :: Int -> Word8 -> Maybe Int
follower Int
acc Word8
r | Word8
r Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0xc0 Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
0x80 = Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Word8 -> Int
combine Int
acc Word8
r)
  follower Int
_ Word8
_                        = Maybe Int
forall a. Maybe a
Nothing

  {-# INLINE get_follower #-}
  get_follower :: Int -> B.ByteString -> Maybe (Int, B.ByteString)
  get_follower :: Int -> ByteString -> Maybe (Int, ByteString)
get_follower Int
acc ByteString
cs = do (Word8
x,ByteString
xs) <- ByteString -> Maybe (Word8, ByteString)
forall b s. UTF8Bytes b s => b -> Maybe (Word8, b)
buncons ByteString
cs
                           Int
acc1 <- Int -> Word8 -> Maybe Int
follower Int
acc Word8
x
                           (Int, ByteString) -> Maybe (Int, ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
acc1,ByteString
xs)

  bytes2 :: Int -> B.ByteString -> (Char, Int)
  bytes2 :: Int -> ByteString -> (Char, Int)
bytes2 Int
c ByteString
cs = case Int -> ByteString -> Maybe (Int, ByteString)
get_follower Int
c ByteString
cs of
                  Just (Int
d, ByteString
_) | Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0x80  -> (Int -> Char
forall a. Enum a => Int -> a
toEnum Int
d, Int
2)
                              | Bool
otherwise  -> (Char
replacement_char, Int
1)
                  Maybe (Int, ByteString)
_ -> (Char
replacement_char, Int
1)

  bytes3 :: Int -> B.ByteString -> (Char, Int)
  bytes3 :: Int -> ByteString -> (Char, Int)
bytes3 Int
c ByteString
cs =
    case Int -> ByteString -> Maybe (Int, ByteString)
get_follower Int
c ByteString
cs of
      Just (Int
d1, ByteString
cs1) ->
        case Int -> ByteString -> Maybe (Int, ByteString)
get_follower Int
d1 ByteString
cs1 of
          Just (Int
d, ByteString
_) | (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0x800 Bool -> Bool -> Bool
&& Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0xd800) Bool -> Bool -> Bool
||
                        (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0xdfff Bool -> Bool -> Bool
&& Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0xfffe) -> (Int -> Char
forall a. Enum a => Int -> a
toEnum Int
d, Int
3)
                      | Bool
otherwise -> (Char
replacement_char, Int
3)
          Maybe (Int, ByteString)
_ -> (Char
replacement_char, Int
2)
      Maybe (Int, ByteString)
_ -> (Char
replacement_char, Int
1)

  bytes4 :: Int -> B.ByteString -> (Char, Int)
  bytes4 :: Int -> ByteString -> (Char, Int)
bytes4 Int
c ByteString
cs =
    case Int -> ByteString -> Maybe (Int, ByteString)
get_follower Int
c ByteString
cs of
      Just (Int
d1, ByteString
cs1) ->
        case Int -> ByteString -> Maybe (Int, ByteString)
get_follower Int
d1 ByteString
cs1 of
          Just (Int
d2, ByteString
cs2) ->
            case Int -> ByteString -> Maybe (Int, ByteString)
get_follower Int
d2 ByteString
cs2 of
              Just (Int
d,ByteString
_) | Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0x10000 Bool -> Bool -> Bool
&& Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0x110000 -> (Int -> Char
forall a. Enum a => Int -> a
toEnum Int
d, Int
4)
                         | Bool
otherwise                    -> (Char
replacement_char, Int
4)
              Maybe (Int, ByteString)
_ -> (Char
replacement_char, Int
3)
          Maybe (Int, ByteString)
_ -> (Char
replacement_char, Int
2)
      Maybe (Int, ByteString)
_ -> (Char
replacement_char, Int
1)


-- | Split after a given number of characters.
-- Negative values are treated as if they are 0.
splitAt :: Int -> B.ByteString -> (B.ByteString,B.ByteString)
splitAt :: Int -> ByteString -> (ByteString, ByteString)
splitAt Int
x ByteString
bs = Int -> Int -> ByteString -> (ByteString, ByteString)
forall t.
(Ord t, Num t) =>
Int -> t -> ByteString -> (ByteString, ByteString)
loop Int
0 Int
x ByteString
bs
  where loop :: Int -> t -> ByteString -> (ByteString, ByteString)
loop Int
a t
n ByteString
_ | t
n t -> t -> Bool
forall a. Ord a => a -> a -> Bool
<= t
0 = Int -> ByteString -> (ByteString, ByteString)
B.splitAt Int
a ByteString
bs
        loop Int
a t
n ByteString
bs1 = case ByteString -> Maybe (Char, Int)
decode ByteString
bs1 of
                         Just (Char
_,Int
y) -> Int -> t -> ByteString -> (ByteString, ByteString)
loop (Int
aInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
y) (t
nt -> t -> t
forall a. Num a => a -> a -> a
-t
1) (Int -> ByteString -> ByteString
B.drop Int
y ByteString
bs1)
                         Maybe (Char, Int)
Nothing    -> (ByteString
bs, ByteString
B.empty)

-- | @take n s@ returns the first @n@ characters of @s@.
-- If @s@ has less than @n@ characters, then we return the whole of @s@.
take :: Int -> B.ByteString -> B.ByteString
take :: Int -> ByteString -> ByteString
take Int
n ByteString
bs = (ByteString, ByteString) -> ByteString
forall a b. (a, b) -> a
fst (Int -> ByteString -> (ByteString, ByteString)
splitAt Int
n ByteString
bs)

-- | @drop n s@ returns the @s@ without its first @n@ characters.
-- If @s@ has less than @n@ characters, then we return an empty string.
drop :: Int -> B.ByteString -> B.ByteString
drop :: Int -> ByteString -> ByteString
drop Int
n ByteString
bs = (ByteString, ByteString) -> ByteString
forall a b. (a, b) -> b
snd (Int -> ByteString -> (ByteString, ByteString)
splitAt Int
n ByteString
bs)

-- | Split a string into two parts:  the first is the longest prefix
-- that contains only characters that satisfy the predicate; the second
-- part is the rest of the string.
-- Invalid characters are passed as @\'\\0xFFFD\'@ to the predicate.
span :: (Char -> Bool) -> B.ByteString -> (B.ByteString, B.ByteString)
span :: (Char -> Bool) -> ByteString -> (ByteString, ByteString)
span Char -> Bool
p ByteString
bs = Int -> ByteString -> (ByteString, ByteString)
loop Int
0 ByteString
bs
  where loop :: Int -> ByteString -> (ByteString, ByteString)
loop Int
a ByteString
cs = case ByteString -> Maybe (Char, Int)
decode ByteString
cs of
                      Just (Char
c,Int
n) | Char -> Bool
p Char
c -> Int -> ByteString -> (ByteString, ByteString)
loop (Int
aInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
n) (Int -> ByteString -> ByteString
B.drop Int
n ByteString
cs)
                      Maybe (Char, Int)
_ -> Int -> ByteString -> (ByteString, ByteString)
B.splitAt Int
a ByteString
bs

-- | Split a string into two parts:  the first is the longest prefix
-- that contains only characters that do not satisfy the predicate; the second
-- part is the rest of the string.
-- Invalid characters are passed as @\'\\0xFFFD\'@ to the predicate.
break :: (Char -> Bool) -> B.ByteString -> (B.ByteString, B.ByteString)
break :: (Char -> Bool) -> ByteString -> (ByteString, ByteString)
break Char -> Bool
p ByteString
bs = (Char -> Bool) -> ByteString -> (ByteString, ByteString)
span (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
p) ByteString
bs

-- | Get the first character of a byte string, if any.
-- Malformed characters are replaced by @\'\\0xFFFD\'@.
uncons :: B.ByteString -> Maybe (Char,B.ByteString)
uncons :: ByteString -> Maybe (Char, ByteString)
uncons ByteString
bs = do (Char
c,Int
n) <- ByteString -> Maybe (Char, Int)
decode ByteString
bs
               (Char, ByteString) -> Maybe (Char, ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Char
c, Int -> ByteString -> ByteString
B.drop Int
n ByteString
bs)

-- | Traverse a bytestring (right biased).
foldr :: (Char -> a -> a) -> a -> B.ByteString -> a
foldr :: (Char -> a -> a) -> a -> ByteString -> a
foldr Char -> a -> a
cons a
nil ByteString
cs = case ByteString -> Maybe (Char, ByteString)
uncons ByteString
cs of
                      Just (Char
a,ByteString
as) -> Char -> a -> a
cons Char
a ((Char -> a -> a) -> a -> ByteString -> a
forall a. (Char -> a -> a) -> a -> ByteString -> a
foldr Char -> a -> a
cons a
nil ByteString
as)
                      Maybe (Char, ByteString)
Nothing     -> a
nil

-- | Traverse a bytestring (left biased).
-- This function is strict in the accumulator.
foldl :: (a -> Char -> a) -> a -> B.ByteString -> a
foldl :: (a -> Char -> a) -> a -> ByteString -> a
foldl a -> Char -> a
add a
acc ByteString
cs  = case ByteString -> Maybe (Char, ByteString)
uncons ByteString
cs of
                      Just (Char
a,ByteString
as) -> let v :: a
v = a -> Char -> a
add a
acc Char
a
                                     in a -> a -> a
seq a
v ((a -> Char -> a) -> a -> ByteString -> a
forall a. (a -> Char -> a) -> a -> ByteString -> a
foldl a -> Char -> a
add a
v ByteString
as)
                      Maybe (Char, ByteString)
Nothing     -> a
acc

-- | Counts the number of characters encoded in the bytestring.
-- Note that this includes replacement characters.
length :: B.ByteString -> Int
length :: ByteString -> Int
length ByteString
b = Int -> ByteString -> Int
forall p. Num p => p -> ByteString -> p
loop Int
0 ByteString
b
  where loop :: p -> ByteString -> p
loop p
n ByteString
xs = case ByteString -> Maybe (Char, Int)
decode ByteString
xs of
                      Just (Char
_,Int
m) -> p -> ByteString -> p
loop (p
np -> p -> p
forall a. Num a => a -> a -> a
+p
1) (Int -> ByteString -> ByteString
B.drop Int
m ByteString
xs)
                      Maybe (Char, Int)
Nothing -> p
n

-- | Split a string into a list of lines.
-- Lines are terminated by @\'\\n\'@ or the end of the string.
-- Empty lines may not be terminated by the end of the string.
-- See also 'lines''.
lines :: B.ByteString -> [B.ByteString]
lines :: ByteString -> [ByteString]
lines ByteString
bs | ByteString -> Bool
B.null ByteString
bs  = []
lines ByteString
bs = case Word8 -> ByteString -> Maybe Int
B.elemIndex Word8
10 ByteString
bs of
             Just Int
x -> let (ByteString
xs,ByteString
ys) = Int -> ByteString -> (ByteString, ByteString)
B.splitAt Int
x ByteString
bs
                       in ByteString
xs ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
: ByteString -> [ByteString]
lines (ByteString -> ByteString
B.tail ByteString
ys)
             Maybe Int
Nothing -> [ByteString
bs]

-- | Split a string into a list of lines.
-- Lines are terminated by @\'\\n\'@ or the end of the string.
-- Empty lines may not be terminated by the end of the string.
-- This function preserves the terminators.
-- See also 'lines'.
lines' :: B.ByteString -> [B.ByteString]
lines' :: ByteString -> [ByteString]
lines' ByteString
bs | ByteString -> Bool
B.null ByteString
bs  = []
lines' ByteString
bs = case Word8 -> ByteString -> Maybe Int
B.elemIndex Word8
10 ByteString
bs of
              Just Int
x -> let (ByteString
xs,ByteString
ys) = Int -> ByteString -> (ByteString, ByteString)
B.splitAt (Int
xInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) ByteString
bs
                        in ByteString
xs ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
: ByteString -> [ByteString]
lines' ByteString
ys
              Maybe Int
Nothing -> [ByteString
bs]