{-# LANGUAGE CPP, BangPatterns #-}
#if __GLASGOW_HASKELL__ >= 701
{-# LANGUAGE Trustworthy #-}
#endif
module Data.ByteString.Lazy.UTF8
( B.ByteString
, decode
, replacement_char
, uncons
, splitAt
, take
, drop
, span
, break
, fromString
, toString
, foldl
, foldr
, length
, lines
, lines'
) where
import Data.Bits
import Data.Word
import Data.Int
import Foreign.Storable
import Foreign.Ptr
import Foreign.ForeignPtr
import Data.Char (ord)
import Control.Exception (assert)
import qualified Data.ByteString.Lazy as B
import qualified Data.ByteString.Lazy.Internal as B
import qualified Data.ByteString.Internal as S
import Prelude hiding (take,drop,splitAt,span,break,foldr,foldl,length,lines)
import Codec.Binary.UTF8.Generic (buncons)
#if MIN_VERSION_base(4,4,0)
import System.IO.Unsafe (unsafeDupablePerformIO)
#else
import GHC.IO (unsafeDupablePerformIO)
#endif
fromString :: String -> B.ByteString
fromString :: String -> ByteString
fromString [] = ByteString
B.empty
fromString String
xs0 = Int -> String -> ByteString
packChunks Int
32 String
xs0
where
packChunks :: Int -> String -> ByteString
packChunks Int
n String
xs = case Int -> String -> (ByteString, String)
packUptoLenBytes Int
n String
xs of
(ByteString
bs, [] ) -> ByteString -> ByteString -> ByteString
B.chunk ByteString
bs ByteString
B.Empty
(ByteString
bs, String
xs') -> ByteString -> ByteString -> ByteString
B.Chunk ByteString
bs (Int -> String -> ByteString
packChunks (forall a. Ord a => a -> a -> a
min (Int
n forall a. Num a => a -> a -> a
* Int
2) Int
B.smallChunkSize) String
xs')
packUptoLenBytes :: Int -> String -> (S.ByteString, String)
packUptoLenBytes :: Int -> String -> (ByteString, String)
packUptoLenBytes Int
len String
xs = forall a. Int -> (Ptr Word8 -> IO (Int, a)) -> (ByteString, a)
unsafeCreateUptoN' Int
len forall a b. (a -> b) -> a -> b
$ \Ptr Word8
ptr -> do
(Ptr Word8
end, String
xs') <- Ptr Word8 -> Ptr Word8 -> String -> IO (Ptr Word8, String)
go Ptr Word8
ptr (Ptr Word8
ptr forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
lenforall a. Num a => a -> a -> a
-Int
4)) String
xs
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Word8
end forall a b. Ptr a -> Ptr b -> Int
`minusPtr` Ptr Word8
ptr, String
xs')
go :: Ptr Word8 -> Ptr Word8 -> String -> IO (Ptr Word8, String)
go :: Ptr Word8 -> Ptr Word8 -> String -> IO (Ptr Word8, String)
go !Ptr Word8
ptr !Ptr Word8
end String
xs | Ptr Word8
ptr forall a. Ord a => a -> a -> Bool
> Ptr Word8
end = forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Word8
ptr, String
xs)
go !Ptr Word8
ptr !Ptr Word8
_ [] = forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Word8
ptr, [])
go !Ptr Word8
ptr !Ptr Word8
end (Char
x:String
xs)
| Char
x forall a. Ord a => a -> a -> Bool
<= Char
'\x7f' = forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word8
ptr (Char -> Word8
S.c2w Char
x) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Word8 -> Ptr Word8 -> String -> IO (Ptr Word8, String)
go (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
ptr Int
1) Ptr Word8
end String
xs
| Bool
otherwise = case Char -> Int
ord Char
x of
Int
oc | Int
oc forall a. Ord a => a -> a -> Bool
<= Int
0x7ff -> do
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word8
ptr forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Int
0xc0 forall a. Num a => a -> a -> a
+ (Int
oc forall a. Bits a => a -> Int -> a
`shiftR` Int
6)
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr Word8
ptr Int
1 forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Int
0x80 forall a. Num a => a -> a -> a
+ Int
oc forall a. Bits a => a -> a -> a
.&. Int
0x3f
Ptr Word8 -> Ptr Word8 -> String -> IO (Ptr Word8, String)
go (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
ptr Int
2) Ptr Word8
end String
xs
| Int
oc forall a. Ord a => a -> a -> Bool
<= Int
0xffff -> do
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word8
ptr forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Int
0xe0 forall a. Num a => a -> a -> a
+ (Int
oc forall a. Bits a => a -> Int -> a
`shiftR` Int
12)
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr Word8
ptr Int
1 forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Int
0x80 forall a. Num a => a -> a -> a
+ ((Int
oc forall a. Bits a => a -> Int -> a
`shiftR` Int
6) forall a. Bits a => a -> a -> a
.&. Int
0x3f)
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr Word8
ptr Int
2 forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Int
0x80 forall a. Num a => a -> a -> a
+ Int
oc forall a. Bits a => a -> a -> a
.&. Int
0x3f
Ptr Word8 -> Ptr Word8 -> String -> IO (Ptr Word8, String)
go (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
ptr Int
3) Ptr Word8
end String
xs
| Bool
otherwise -> do
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word8
ptr forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Int
0xf0 forall a. Num a => a -> a -> a
+ (Int
oc forall a. Bits a => a -> Int -> a
`shiftR` Int
18)
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr Word8
ptr Int
1 forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Int
0x80 forall a. Num a => a -> a -> a
+ ((Int
oc forall a. Bits a => a -> Int -> a
`shiftR` Int
12) forall a. Bits a => a -> a -> a
.&. Int
0x3f)
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr Word8
ptr Int
2 forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Int
0x80 forall a. Num a => a -> a -> a
+ ((Int
oc forall a. Bits a => a -> Int -> a
`shiftR` Int
6) forall a. Bits a => a -> a -> a
.&. Int
0x3f)
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr Word8
ptr Int
3 forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Int
0x80 forall a. Num a => a -> a -> a
+ Int
oc forall a. Bits a => a -> a -> a
.&. Int
0x3f
Ptr Word8 -> Ptr Word8 -> String -> IO (Ptr Word8, String)
go (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
ptr Int
4) Ptr Word8
end String
xs
toString :: B.ByteString -> String
toString :: ByteString -> String
toString ByteString
bs = forall a. (Char -> a -> a) -> a -> ByteString -> a
foldr (:) [] ByteString
bs
replacement_char :: Char
replacement_char :: Char
replacement_char = Char
'\xfffd'
decode :: B.ByteString -> Maybe (Char,Int64)
decode :: ByteString -> Maybe (Char, Int64)
decode ByteString
bs = do (Word8
c,ByteString
cs) <- forall b s. UTF8Bytes b s => b -> Maybe (Word8, b)
buncons ByteString
bs
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> ByteString -> (Char, Int64)
choose (forall a. Enum a => a -> Int
fromEnum Word8
c) ByteString
cs)
where
choose :: Int -> B.ByteString -> (Char, Int64)
choose :: Int -> ByteString -> (Char, Int64)
choose Int
c ByteString
cs
| Int
c forall a. Ord a => a -> a -> Bool
< Int
0x80 = (forall a. Enum a => Int -> a
toEnum forall a b. (a -> b) -> a -> b
$ forall a. Enum a => a -> Int
fromEnum Int
c, Int64
1)
| Int
c forall a. Ord a => a -> a -> Bool
< Int
0xc0 = (Char
replacement_char, Int64
1)
| Int
c forall a. Ord a => a -> a -> Bool
< Int
0xe0 = Int -> ByteString -> (Char, Int64)
bytes2 (Int -> Int -> Int
mask Int
c Int
0x1f) ByteString
cs
| Int
c forall a. Ord a => a -> a -> Bool
< Int
0xf0 = Int -> ByteString -> (Char, Int64)
bytes3 (Int -> Int -> Int
mask Int
c Int
0x0f) ByteString
cs
| Int
c forall a. Ord a => a -> a -> Bool
< Int
0xf8 = Int -> ByteString -> (Char, Int64)
bytes4 (Int -> Int -> Int
mask Int
c Int
0x07) ByteString
cs
| Bool
otherwise = (Char
replacement_char, Int64
1)
mask :: Int -> Int -> Int
mask :: Int -> Int -> Int
mask Int
c Int
m = forall a. Enum a => a -> Int
fromEnum (Int
c forall a. Bits a => a -> a -> a
.&. Int
m)
combine :: Int -> Word8 -> Int
combine :: Int -> Word8 -> Int
combine Int
acc Word8
r = forall a. Bits a => a -> Int -> a
shiftL Int
acc Int
6 forall a. Bits a => a -> a -> a
.|. forall a. Enum a => a -> Int
fromEnum (Word8
r 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 forall a. Bits a => a -> a -> a
.&. Word8
0xc0 forall a. Eq a => a -> a -> Bool
== Word8
0x80 = forall a. a -> Maybe a
Just (Int -> Word8 -> Int
combine Int
acc Word8
r)
follower Int
_ Word8
_ = 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) <- forall b s. UTF8Bytes b s => b -> Maybe (Word8, b)
buncons ByteString
cs
Int
acc1 <- Int -> Word8 -> Maybe Int
follower Int
acc Word8
x
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
acc1,ByteString
xs)
bytes2 :: Int -> B.ByteString -> (Char, Int64)
bytes2 :: Int -> ByteString -> (Char, Int64)
bytes2 Int
c ByteString
cs = case Int -> ByteString -> Maybe (Int, ByteString)
get_follower Int
c ByteString
cs of
Just (Int
d, ByteString
_) | Int
d forall a. Ord a => a -> a -> Bool
>= Int
0x80 -> (forall a. Enum a => Int -> a
toEnum Int
d, Int64
2)
| Bool
otherwise -> (Char
replacement_char, Int64
1)
Maybe (Int, ByteString)
_ -> (Char
replacement_char, Int64
1)
bytes3 :: Int -> B.ByteString -> (Char, Int64)
bytes3 :: Int -> ByteString -> (Char, Int64)
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 forall a. Ord a => a -> a -> Bool
>= Int
0x800 Bool -> Bool -> Bool
&& Int
d forall a. Ord a => a -> a -> Bool
< Int
0xd800) Bool -> Bool -> Bool
||
(Int
d forall a. Ord a => a -> a -> Bool
> Int
0xdfff Bool -> Bool -> Bool
&& Int
d forall a. Ord a => a -> a -> Bool
< Int
0xfffe) -> (forall a. Enum a => Int -> a
toEnum Int
d, Int64
3)
| Bool
otherwise -> (Char
replacement_char, Int64
3)
Maybe (Int, ByteString)
_ -> (Char
replacement_char, Int64
2)
Maybe (Int, ByteString)
_ -> (Char
replacement_char, Int64
1)
bytes4 :: Int -> B.ByteString -> (Char, Int64)
bytes4 :: Int -> ByteString -> (Char, Int64)
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 forall a. Ord a => a -> a -> Bool
>= Int
0x10000 Bool -> Bool -> Bool
&& Int
d forall a. Ord a => a -> a -> Bool
< Int
0x110000 -> (forall a. Enum a => Int -> a
toEnum Int
d, Int64
4)
| Bool
otherwise -> (Char
replacement_char, Int64
4)
Maybe (Int, ByteString)
_ -> (Char
replacement_char, Int64
3)
Maybe (Int, ByteString)
_ -> (Char
replacement_char, Int64
2)
Maybe (Int, ByteString)
_ -> (Char
replacement_char, Int64
1)
{-# INLINE decode #-}
splitAt :: Int64 -> B.ByteString -> (B.ByteString,B.ByteString)
splitAt :: Int64 -> ByteString -> (ByteString, ByteString)
splitAt Int64
x ByteString
bs = forall {t}.
(Ord t, Num t) =>
Int64 -> t -> ByteString -> (ByteString, ByteString)
loop Int64
0 Int64
x ByteString
bs
where loop :: Int64 -> t -> ByteString -> (ByteString, ByteString)
loop !Int64
a t
n ByteString
_ | t
n forall a. Ord a => a -> a -> Bool
<= t
0 = Int64 -> ByteString -> (ByteString, ByteString)
B.splitAt Int64
a ByteString
bs
loop !Int64
a t
n ByteString
bs1 = case ByteString -> Maybe (Char, Int64)
decode ByteString
bs1 of
Just (Char
_,Int64
y) -> Int64 -> t -> ByteString -> (ByteString, ByteString)
loop (Int64
aforall a. Num a => a -> a -> a
+Int64
y) (t
nforall a. Num a => a -> a -> a
-t
1) (Int64 -> ByteString -> ByteString
B.drop Int64
y ByteString
bs1)
Maybe (Char, Int64)
Nothing -> (ByteString
bs, ByteString
B.empty)
take :: Int64 -> B.ByteString -> B.ByteString
take :: Int64 -> ByteString -> ByteString
take Int64
x ByteString
bs = forall {t}.
(Ord t, Num t) =>
Int64 -> t -> ByteString -> ByteString
loop Int64
0 Int64
x ByteString
bs
where loop :: Int64 -> t -> ByteString -> ByteString
loop !Int64
a t
n ByteString
_ | t
n forall a. Ord a => a -> a -> Bool
<= t
0 = Int64 -> ByteString -> ByteString
B.take Int64
a ByteString
bs
loop !Int64
a t
n ByteString
bs1 = case ByteString -> Maybe (Char, Int64)
decode ByteString
bs1 of
Just (Char
_,Int64
y) -> Int64 -> t -> ByteString -> ByteString
loop (Int64
aforall a. Num a => a -> a -> a
+Int64
y) (t
nforall a. Num a => a -> a -> a
-t
1) (Int64 -> ByteString -> ByteString
B.drop Int64
y ByteString
bs1)
Maybe (Char, Int64)
Nothing -> ByteString
bs
drop :: Int64 -> B.ByteString -> B.ByteString
drop :: Int64 -> ByteString -> ByteString
drop Int64
x ByteString
bs = forall {t}.
(Ord t, Num t) =>
Int64 -> t -> ByteString -> ByteString
loop Int64
0 Int64
x ByteString
bs
where loop :: Int64 -> t -> ByteString -> ByteString
loop !Int64
a t
n ByteString
_ | t
n forall a. Ord a => a -> a -> Bool
<= t
0 = Int64 -> ByteString -> ByteString
B.drop Int64
a ByteString
bs
loop !Int64
a t
n ByteString
bs1 = case ByteString -> Maybe (Char, Int64)
decode ByteString
bs1 of
Just (Char
_,Int64
y) -> Int64 -> t -> ByteString -> ByteString
loop (Int64
aforall a. Num a => a -> a -> a
+Int64
y) (t
nforall a. Num a => a -> a -> a
-t
1) (Int64 -> ByteString -> ByteString
B.drop Int64
y ByteString
bs1)
Maybe (Char, Int64)
Nothing -> ByteString
B.empty
span :: (Char -> Bool) -> B.ByteString -> (B.ByteString, B.ByteString)
span :: (Char -> Bool) -> ByteString -> (ByteString, ByteString)
span Char -> Bool
p ByteString
bs = Int64 -> ByteString -> (ByteString, ByteString)
loop Int64
0 ByteString
bs
where loop :: Int64 -> ByteString -> (ByteString, ByteString)
loop Int64
a ByteString
cs = case ByteString -> Maybe (Char, Int64)
decode ByteString
cs of
Just (Char
c,Int64
n) | Char -> Bool
p Char
c -> Int64 -> ByteString -> (ByteString, ByteString)
loop (Int64
aforall a. Num a => a -> a -> a
+Int64
n) (Int64 -> ByteString -> ByteString
B.drop Int64
n ByteString
cs)
Maybe (Char, Int64)
_ -> Int64 -> ByteString -> (ByteString, ByteString)
B.splitAt Int64
a ByteString
bs
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 forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
p) ByteString
bs
uncons :: B.ByteString -> Maybe (Char,B.ByteString)
uncons :: ByteString -> Maybe (Char, ByteString)
uncons ByteString
bs = do (Char
c,Int64
n) <- ByteString -> Maybe (Char, Int64)
decode ByteString
bs
forall (m :: * -> *) a. Monad m => a -> m a
return (Char
c, Int64 -> ByteString -> ByteString
B.drop Int64
n ByteString
bs)
foldr :: (Char -> a -> a) -> a -> B.ByteString -> a
foldr :: forall a. (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 (forall a. (Char -> a -> a) -> a -> ByteString -> a
foldr Char -> a -> a
cons a
nil ByteString
as)
Maybe (Char, ByteString)
Nothing -> a
nil
foldl :: (a -> Char -> a) -> a -> B.ByteString -> a
foldl :: forall a. (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 seq :: forall a b. a -> b -> b
seq a
v (forall a. (a -> Char -> a) -> a -> ByteString -> a
foldl a -> Char -> a
add a
v ByteString
as)
Maybe (Char, ByteString)
Nothing -> a
acc
length :: B.ByteString -> Int
length :: ByteString -> Int
length ByteString
b = forall {t}. Num t => t -> ByteString -> t
loop Int
0 ByteString
b
where loop :: t -> ByteString -> t
loop t
n ByteString
xs = case ByteString -> Maybe (Char, Int64)
decode ByteString
xs of
Just (Char
_,Int64
m) -> t -> ByteString -> t
loop (t
nforall a. Num a => a -> a -> a
+t
1) (Int64 -> ByteString -> ByteString
B.drop Int64
m ByteString
xs)
Maybe (Char, Int64)
Nothing -> t
n
lines :: B.ByteString -> [B.ByteString]
lines :: ByteString -> [ByteString]
lines ByteString
bs | ByteString -> Bool
B.null ByteString
bs = []
lines ByteString
bs = case Word8 -> ByteString -> Maybe Int64
B.elemIndex Word8
10 ByteString
bs of
Just Int64
x -> let (ByteString
xs,ByteString
ys) = Int64 -> ByteString -> (ByteString, ByteString)
B.splitAt Int64
x ByteString
bs
in ByteString
xs forall a. a -> [a] -> [a]
: ByteString -> [ByteString]
lines (HasCallStack => ByteString -> ByteString
B.tail ByteString
ys)
Maybe Int64
Nothing -> [ByteString
bs]
lines' :: B.ByteString -> [B.ByteString]
lines' :: ByteString -> [ByteString]
lines' ByteString
bs | ByteString -> Bool
B.null ByteString
bs = []
lines' ByteString
bs = case Word8 -> ByteString -> Maybe Int64
B.elemIndex Word8
10 ByteString
bs of
Just Int64
x -> let (ByteString
xs,ByteString
ys) = Int64 -> ByteString -> (ByteString, ByteString)
B.splitAt (Int64
xforall a. Num a => a -> a -> a
+Int64
1) ByteString
bs
in ByteString
xs forall a. a -> [a] -> [a]
: ByteString -> [ByteString]
lines' ByteString
ys
Maybe Int64
Nothing -> [ByteString
bs]
unsafeCreateUptoN' :: Int -> (Ptr Word8 -> IO (Int, a)) -> (S.ByteString, a)
unsafeCreateUptoN' :: forall a. Int -> (Ptr Word8 -> IO (Int, a)) -> (ByteString, a)
unsafeCreateUptoN' Int
l Ptr Word8 -> IO (Int, a)
f = forall a. IO a -> a
unsafeDupablePerformIO (forall a. Int -> (Ptr Word8 -> IO (Int, a)) -> IO (ByteString, a)
createUptoN' Int
l Ptr Word8 -> IO (Int, a)
f)
{-# INLINE unsafeCreateUptoN' #-}
createUptoN' :: Int -> (Ptr Word8 -> IO (Int, a)) -> IO (S.ByteString, a)
createUptoN' :: forall a. Int -> (Ptr Word8 -> IO (Int, a)) -> IO (ByteString, a)
createUptoN' Int
l Ptr Word8 -> IO (Int, a)
f = do
ForeignPtr Word8
fp <- forall a. Int -> IO (ForeignPtr a)
S.mallocByteString Int
l
(Int
l', a
res) <- forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Word8
fp forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> Ptr Word8 -> IO (Int, a)
f Ptr Word8
p
#if MIN_VERSION_bytestring(0,11,0)
let bs :: ByteString
bs = ForeignPtr Word8 -> Int -> ByteString
S.BS ForeignPtr Word8
fp Int
l'
#else
let bs = S.PS fp 0 l'
#endif
forall a. HasCallStack => Bool -> a -> a
assert (Int
l' forall a. Ord a => a -> a -> Bool
<= Int
l) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString
bs, a
res)
{-# INLINE createUptoN' #-}