{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE TypeApplications #-}
module Data.ByteString.Base16.Internal.W64.Loop
( innerLoop
, decodeLoop
, lenientLoop
) where
import Data.Bits
import Data.ByteString.Internal
import Data.ByteString.Base16.Internal.Utils
import qualified Data.ByteString.Base16.Internal.W32.Loop as W32
import Data.Text (Text)
import qualified Data.Text as T
import Foreign.ForeignPtr
import Foreign.Ptr
import Foreign.Storable
import GHC.Word
innerLoop
:: Ptr Word64
-> Ptr Word32
-> Ptr Word8
-> IO ()
innerLoop :: Ptr Word64 -> Ptr Word32 -> Ptr Word8 -> IO ()
innerLoop !Ptr Word64
dptr !Ptr Word32
sptr !Ptr Word8
end = Ptr Word64 -> Ptr Word32 -> IO ()
go Ptr Word64
dptr Ptr Word32
sptr
where
lix :: a -> Word8
lix !a
a = Word8 -> Addr# -> Word8
aix (a -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
a Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. 0x0f) Addr#
alphabet
{-# INLINE lix #-}
!alphabet :: Addr#
alphabet = "0123456789abcdef"#
go :: Ptr Word64 -> Ptr Word32 -> IO ()
go !Ptr Word64
dst !Ptr Word32
src
| Ptr Word32 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word32
src 7 Ptr Word8 -> Ptr Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Ptr Word8
end =
Ptr Word32 -> Ptr Word16 -> Ptr Word8 -> IO ()
W32.innerLoop (Ptr Word64 -> Ptr Word32
forall a b. Ptr a -> Ptr b
castPtr Ptr Word64
dst) (Ptr Word32 -> Ptr Word16
forall a b. Ptr a -> Ptr b
castPtr Ptr Word32
src) Ptr Word8
end
| Bool
otherwise = do
#ifdef WORDS_BIGENDIAN
!t <- peek src
#else
!Word32
t <- Word32 -> Word32
byteSwap32 (Word32 -> Word32) -> IO Word32 -> IO Word32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 Ptr Word32
src
#endif
let !a :: Word32
a = Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
unsafeShiftR Word32
t 28
!b :: Word32
b = Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
unsafeShiftR Word32
t 24
!c :: Word32
c = Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
unsafeShiftR Word32
t 20
!d :: Word32
d = Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
unsafeShiftR Word32
t 16
!e :: Word32
e = Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
unsafeShiftR Word32
t 12
!f :: Word32
f = Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
unsafeShiftR Word32
t 8
!g :: Word32
g = Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
unsafeShiftR Word32
t 4
let !p :: Word64
p = Word8 -> Word64
w64 (Word32 -> Word8
forall a. Integral a => a -> Word8
lix Word32
a)
!q :: Word64
q = Word8 -> Word64
w64 (Word32 -> Word8
forall a. Integral a => a -> Word8
lix Word32
b)
!r :: Word64
r = Word8 -> Word64
w64 (Word32 -> Word8
forall a. Integral a => a -> Word8
lix Word32
c)
!s :: Word64
s = Word8 -> Word64
w64 (Word32 -> Word8
forall a. Integral a => a -> Word8
lix Word32
d)
!w :: Word64
w = Word8 -> Word64
w64 (Word32 -> Word8
forall a. Integral a => a -> Word8
lix Word32
e)
!x :: Word64
x = Word8 -> Word64
w64 (Word32 -> Word8
forall a. Integral a => a -> Word8
lix Word32
f)
!y :: Word64
y = Word8 -> Word64
w64 (Word32 -> Word8
forall a. Integral a => a -> Word8
lix Word32
g)
!z :: Word64
z = Word8 -> Word64
w64 (Word32 -> Word8
forall a. Integral a => a -> Word8
lix Word32
t)
let !xx :: Word64
xx = Word64
p
Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|. (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
q 8)
Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|. (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
r 16)
Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|. (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
s 24)
!yy :: Word64
yy = Word64
w
Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|. (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
x 8)
Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|. (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
y 16)
Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|. (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
z 24)
let !zz :: Word64
zz = Word64
xx Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|. Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
yy 32
Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word64
dst Word64
zz
Ptr Word64 -> Ptr Word32 -> IO ()
go (Ptr Word64 -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
dst 8) (Ptr Word32 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word32
src 4)
{-# INLINE innerLoop #-}
decodeLoop
:: ForeignPtr Word8
-> Ptr Word8
-> Ptr Word8
-> Ptr Word32
-> Ptr Word64
-> Ptr Word8
-> Int
-> IO (Either Text ByteString)
decodeLoop :: ForeignPtr Word8
-> Ptr Word8
-> Ptr Word8
-> Ptr Word32
-> Ptr Word64
-> Ptr Word8
-> Int
-> IO (Either Text ByteString)
decodeLoop !ForeignPtr Word8
dfp !Ptr Word8
hi !Ptr Word8
lo !Ptr Word32
dptr !Ptr Word64
sptr !Ptr Word8
end !Int
nn = Ptr Word32 -> Ptr Word64 -> Int -> IO (Either Text ByteString)
go Ptr Word32
dptr Ptr Word64
sptr Int
nn
where
err :: Ptr a -> m (Either Text b)
err !Ptr a
src = Either Text b -> m (Either Text b)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either Text b -> m (Either Text b))
-> (String -> Either Text b) -> String -> m (Either Text b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either Text b
forall a b. a -> Either a b
Left (Text -> Either Text b)
-> (String -> Text) -> String -> Either Text b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack
(String -> m (Either Text b)) -> String -> m (Either Text b)
forall a b. (a -> b) -> a -> b
$ "invalid character at offset: "
String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show (Ptr a
src Ptr a -> Ptr Word64 -> Int
forall a b. Ptr a -> Ptr b -> Int
`minusPtr` Ptr Word64
sptr)
go :: Ptr Word32 -> Ptr Word64 -> Int -> IO (Either Text ByteString)
go !Ptr Word32
dst !Ptr Word64
src !Int
n
| Ptr Word64 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src 7 Ptr Word8 -> Ptr Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Ptr Word8
end =
ForeignPtr Word8
-> Ptr Word8
-> Ptr Word8
-> Ptr Word16
-> Ptr Word32
-> Ptr Word8
-> Int
-> IO (Either Text ByteString)
W32.decodeLoop ForeignPtr Word8
dfp Ptr Word8
hi Ptr Word8
lo (Ptr Word32 -> Ptr Word16
forall a b. Ptr a -> Ptr b
castPtr Ptr Word32
dst) (Ptr Word64 -> Ptr Word32
forall a b. Ptr a -> Ptr b
castPtr Ptr Word64
src) Ptr Word8
end Int
n
| Bool
otherwise = do
#ifdef WORDS_BIGENDIAN
!tt <- peek @Word64 src
#else
!Word64
tt <- Word64 -> Word64
byteSwap64 (Word64 -> Word64) -> IO Word64 -> IO Word64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek @Word64 Ptr Word64
src
#endif
let !s :: Int
s = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
tt 56) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. 0xff)
!t :: Int
t = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
tt 48) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. 0xff)
!u :: Int
u = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
tt 40) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. 0xff)
!v :: Int
v = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
tt 32) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. 0xff)
!w :: Int
w = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
tt 24) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. 0xff)
!x :: Int
x = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
tt 16) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. 0xff)
!y :: Int
y = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
tt 8) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. 0xff)
!z :: Int
z = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64
tt Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. 0xff)
!Word8
a <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff @Word8 Ptr Word8
hi Int
s
!Word8
b <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff @Word8 Ptr Word8
lo Int
t
!Word8
c <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff @Word8 Ptr Word8
hi Int
u
!Word8
d <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff @Word8 Ptr Word8
lo Int
v
!Word8
e <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff @Word8 Ptr Word8
hi Int
w
!Word8
f <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff @Word8 Ptr Word8
lo Int
x
!Word8
g <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff @Word8 Ptr Word8
hi Int
y
!Word8
h <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff @Word8 Ptr Word8
lo Int
z
let !zz :: Word32
zz = Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8
a Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.|. Word8
b)
Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. (Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
unsafeShiftL (Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8
c Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.|. Word8
d)) 8)
Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. (Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
unsafeShiftL (Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8
e Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.|. Word8
f)) 16)
Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. (Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
unsafeShiftL (Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8
g Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.|. Word8
h)) 24)
if
| Word8
a Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== 0xff -> Ptr Word64 -> IO (Either Text ByteString)
forall (m :: * -> *) a b. Monad m => Ptr a -> m (Either Text b)
err Ptr Word64
src
| Word8
b Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== 0xff -> Ptr Any -> IO (Either Text ByteString)
forall (m :: * -> *) a b. Monad m => Ptr a -> m (Either Text b)
err (Ptr Word64 -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src 1)
| Word8
c Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== 0xff -> Ptr Any -> IO (Either Text ByteString)
forall (m :: * -> *) a b. Monad m => Ptr a -> m (Either Text b)
err (Ptr Word64 -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src 2)
| Word8
d Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== 0xff -> Ptr Any -> IO (Either Text ByteString)
forall (m :: * -> *) a b. Monad m => Ptr a -> m (Either Text b)
err (Ptr Word64 -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src 3)
| Word8
e Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== 0xff -> Ptr Any -> IO (Either Text ByteString)
forall (m :: * -> *) a b. Monad m => Ptr a -> m (Either Text b)
err (Ptr Word64 -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src 4)
| Word8
f Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== 0xff -> Ptr Any -> IO (Either Text ByteString)
forall (m :: * -> *) a b. Monad m => Ptr a -> m (Either Text b)
err (Ptr Word64 -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src 5)
| Word8
g Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== 0xff -> Ptr Any -> IO (Either Text ByteString)
forall (m :: * -> *) a b. Monad m => Ptr a -> m (Either Text b)
err (Ptr Word64 -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src 6)
| Word8
h Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== 0xff -> Ptr Any -> IO (Either Text ByteString)
forall (m :: * -> *) a b. Monad m => Ptr a -> m (Either Text b)
err (Ptr Word64 -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src 7)
| Bool
otherwise -> do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke @Word32 Ptr Word32
dst Word32
zz
Ptr Word32 -> Ptr Word64 -> Int -> IO (Either Text ByteString)
go (Ptr Word32 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word32
dst 4) (Ptr Word64 -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src 8) (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 4)
{-# INLINE decodeLoop #-}
lenientLoop
:: ForeignPtr Word8
-> Ptr Word8
-> Ptr Word8
-> Ptr Word8
-> Ptr Word8
-> Ptr Word8
-> Int
-> IO ByteString
lenientLoop :: ForeignPtr Word8
-> Ptr Word8
-> Ptr Word8
-> Ptr Word8
-> Ptr Word8
-> Ptr Word8
-> Int
-> IO ByteString
lenientLoop !ForeignPtr Word8
dfp !Ptr Word8
hi !Ptr Word8
lo !Ptr Word8
dptr !Ptr Word8
sptr !Ptr Word8
end !Int
nn =
ForeignPtr Word8
-> Ptr Word8
-> Ptr Word8
-> Ptr Word8
-> Ptr Word8
-> Ptr Word8
-> Int
-> IO ByteString
W32.lenientLoop ForeignPtr Word8
dfp Ptr Word8
hi Ptr Word8
lo Ptr Word8
dptr Ptr Word8
sptr Ptr Word8
end Int
nn