{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE UnboxedTuples #-}
module Data.ByteString.Base16.Internal.Utils
( aix
, reChunk
, runShortST
, runDecodeST
, runDecodeST'
) where
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import Data.ByteString.Short.Internal
import Data.Primitive.ByteArray
import Data.Text (Text)
import GHC.Exts
import GHC.Word
import GHC.ST (ST(..))
aix :: Word8 -> Addr# -> Word8
aix :: Word8 -> Addr# -> Word8
aix Word8
w Addr#
alpha = Word8# -> Word8
W8# (Addr# -> Int# -> Word8#
indexWord8OffAddr# Addr#
alpha Int#
i)
where
!(I# Int#
i) = forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w
{-# INLINE aix #-}
reChunk :: [ByteString] -> [ByteString]
reChunk :: [ByteString] -> [ByteString]
reChunk [] = []
reChunk (ByteString
c:[ByteString]
cs) = case ByteString -> Int
B.length ByteString
c forall a. Integral a => a -> a -> (a, a)
`divMod` Int
2 of
(Int
_, Int
0) -> ByteString
c forall a. a -> [a] -> [a]
: [ByteString] -> [ByteString]
reChunk [ByteString]
cs
(Int
n, Int
_) -> case Int -> ByteString -> (ByteString, ByteString)
B.splitAt (Int
n forall a. Num a => a -> a -> a
* Int
2) ByteString
c of
~(ByteString
m, ByteString
q) -> ByteString
m forall a. a -> [a] -> [a]
: ByteString -> [ByteString] -> [ByteString]
cont_ ByteString
q [ByteString]
cs
where
cont_ :: ByteString -> [ByteString] -> [ByteString]
cont_ ByteString
q [] = [ByteString
q]
cont_ ByteString
q (ByteString
a:[ByteString]
as) = case Int -> ByteString -> (ByteString, ByteString)
B.splitAt Int
1 ByteString
a of
(ByteString
x, ByteString
y) -> let q' :: ByteString
q' = ByteString -> ByteString -> ByteString
B.append ByteString
q ByteString
x
in if ByteString -> Int
B.length ByteString
q' forall a. Eq a => a -> a -> Bool
== Int
2
then
let as' :: [ByteString]
as' = if ByteString -> Bool
B.null ByteString
y then [ByteString]
as else ByteString
yforall a. a -> [a] -> [a]
:[ByteString]
as
in ByteString
q' forall a. a -> [a] -> [a]
: [ByteString] -> [ByteString]
reChunk [ByteString]
as'
else ByteString -> [ByteString] -> [ByteString]
cont_ ByteString
q' [ByteString]
as
runShortST :: (forall s. ST s ByteArray) -> ShortByteString
runShortST :: (forall s. ST s ByteArray) -> ShortByteString
runShortST forall s. ST s ByteArray
enc = forall o. (State# RealWorld -> o) -> o
runRW# forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s0 -> case forall s. ST s ByteArray
enc of
{ ST STRep RealWorld ByteArray
g -> case STRep RealWorld ByteArray
g State# RealWorld
s0 of
{ (# State# RealWorld
_, ByteArray ByteArray#
r #) -> ByteArray# -> ShortByteString
SBS ByteArray#
r
}
}
{-# INLINE runShortST #-}
runDecodeST
:: (forall s. ST s (Either Text ByteArray))
-> Either Text ShortByteString
runDecodeST :: (forall s. ST s (Either Text ByteArray))
-> Either Text ShortByteString
runDecodeST forall s. ST s (Either Text ByteArray)
dec = forall o. (State# RealWorld -> o) -> o
runRW# forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s0 -> case forall s. ST s (Either Text ByteArray)
dec of
{ ST STRep RealWorld (Either Text ByteArray)
g -> case STRep RealWorld (Either Text ByteArray)
g State# RealWorld
s0 of
{ (# State# RealWorld
_, Either Text ByteArray
e #) -> case Either Text ByteArray
e of
Left Text
t -> forall a b. a -> Either a b
Left Text
t
Right (ByteArray ByteArray#
r) -> forall a b. b -> Either a b
Right (ByteArray# -> ShortByteString
SBS ByteArray#
r)
}
}
{-# INLINE runDecodeST #-}
runDecodeST'
:: (forall s. ST s ByteArray)
-> ShortByteString
runDecodeST' :: (forall s. ST s ByteArray) -> ShortByteString
runDecodeST' forall s. ST s ByteArray
dec = forall o. (State# RealWorld -> o) -> o
runRW# forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s0 -> case forall s. ST s ByteArray
dec of
{ ST STRep RealWorld ByteArray
g -> case STRep RealWorld ByteArray
g State# RealWorld
s0 of
(# State# RealWorld
_, ByteArray ByteArray#
r #) -> ByteArray# -> ShortByteString
SBS ByteArray#
r
}
{-# inline runDecodeST' #-}