{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE TypeApplications #-}
module Data.ByteString.Base32.Internal.Loop
( innerLoop
, decodeLoop
) where
import Data.Bits
import Data.ByteString.Internal (ByteString(..))
import Data.ByteString.Base32.Internal.Utils
import Data.Text (Text)
import qualified Data.Text as T
import Foreign.Ptr
import Foreign.ForeignPtr
import Foreign.Storable
import GHC.Exts
import GHC.Word
innerLoop
:: Addr#
-> Ptr Word64
-> Ptr Word8
-> Ptr Word8
-> (Ptr Word8 -> Ptr Word8 -> IO ByteString)
-> IO ByteString
innerLoop :: Addr#
-> Ptr Word64
-> Ptr Word8
-> Ptr Word8
-> (Ptr Word8 -> Ptr Word8 -> IO ByteString)
-> IO ByteString
innerLoop !Addr#
lut !Ptr Word64
dptr !Ptr Word8
sptr !Ptr Word8
end Ptr Word8 -> Ptr Word8 -> IO ByteString
finish = Ptr Word64 -> Ptr Word8 -> IO ByteString
go Ptr Word64
dptr Ptr Word8
sptr
where
lix :: a -> Word64
lix a
a = Word8 -> Word64
w64 (Word8 -> Addr# -> Word8
aix (forall a b. (Integral a, Num b) => a -> b
fromIntegral a
a forall a. Bits a => a -> a -> a
.&. Word8
0x1f) Addr#
lut)
{-# INLINE lix #-}
go :: Ptr Word64 -> Ptr Word8 -> IO ByteString
go !Ptr Word64
dst !Ptr Word8
src
| forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
src Int
4 forall a. Ord a => a -> a -> Bool
>= Ptr Word8
end = Ptr Word8 -> Ptr Word8 -> IO ByteString
finish (forall a b. Ptr a -> Ptr b
castPtr Ptr Word64
dst) Ptr Word8
src
| Bool
otherwise = do
!Word32
t <- Ptr Word32 -> IO Word32
peekWord32BE (forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
src)
!Word32
u <- Word8 -> Word32
w32 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Storable a => Ptr a -> IO a
peek (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
src Int
4)
let !a :: Word64
a = forall {a}. Integral a => a -> Word64
lix (forall a. Bits a => a -> Int -> a
unsafeShiftR Word32
t Int
27)
!b :: Word64
b = forall {a}. Integral a => a -> Word64
lix (forall a. Bits a => a -> Int -> a
unsafeShiftR Word32
t Int
22)
!c :: Word64
c = forall {a}. Integral a => a -> Word64
lix (forall a. Bits a => a -> Int -> a
unsafeShiftR Word32
t Int
17)
!d :: Word64
d = forall {a}. Integral a => a -> Word64
lix (forall a. Bits a => a -> Int -> a
unsafeShiftR Word32
t Int
12)
!e :: Word64
e = forall {a}. Integral a => a -> Word64
lix (forall a. Bits a => a -> Int -> a
unsafeShiftR Word32
t Int
7)
!f :: Word64
f = forall {a}. Integral a => a -> Word64
lix (forall a. Bits a => a -> Int -> a
unsafeShiftR Word32
t Int
2)
!g :: Word64
g = forall {a}. Integral a => a -> Word64
lix (forall a. Bits a => a -> Int -> a
unsafeShiftL Word32
t Int
3 forall a. Bits a => a -> a -> a
.|. forall a. Bits a => a -> Int -> a
unsafeShiftR Word32
u Int
5)
!h :: Word64
h = forall {a}. Integral a => a -> Word64
lix Word32
u
let !w :: Word64
w = Word64
a
forall a. Bits a => a -> a -> a
.|. forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
b Int
8
forall a. Bits a => a -> a -> a
.|. forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
c Int
16
forall a. Bits a => a -> a -> a
.|. forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
d Int
24
forall a. Bits a => a -> a -> a
.|. forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
e Int
32
forall a. Bits a => a -> a -> a
.|. forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
f Int
40
forall a. Bits a => a -> a -> a
.|. forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
g Int
48
forall a. Bits a => a -> a -> a
.|. forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
h Int
56
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word64
dst Word64
w
Ptr Word64 -> Ptr Word8 -> IO ByteString
go (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
dst Int
8) (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
src Int
5)
{-# INLINE innerLoop #-}
decodeLoop
:: Addr#
-> ForeignPtr Word8
-> Ptr Word8
-> Ptr Word64
-> Ptr Word8
-> IO (Either Text ByteString)
decodeLoop :: Addr#
-> ForeignPtr Word8
-> Ptr Word8
-> Ptr Word64
-> Ptr Word8
-> IO (Either Text ByteString)
decodeLoop !Addr#
lut !ForeignPtr Word8
dfp !Ptr Word8
dptr !Ptr Word64
sptr !Ptr Word8
end = Ptr Word8 -> Ptr Word64 -> IO (Either Text ByteString)
go Ptr Word8
dptr Ptr Word64
sptr
where
lix :: a -> Word64
lix a
a = Word8 -> Word64
w64 (Word8 -> Addr# -> Word8
aix (forall a b. (Integral a, Num b) => a -> b
fromIntegral a
a) Addr#
lut)
err :: Ptr Word64 -> IO (Either Text ByteString)
err :: Ptr Word64 -> IO (Either Text ByteString)
err Ptr Word64
p = forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> Either a b
Left forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack
forall a b. (a -> b) -> a -> b
$ String
"invalid character at offset: "
forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (Ptr Word64
p forall a b. Ptr a -> Ptr b -> Int
`minusPtr` Ptr Word64
sptr)
padErr :: Ptr Word64 -> IO (Either Text ByteString)
padErr :: Ptr Word64 -> IO (Either Text ByteString)
padErr Ptr Word64
p = forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> Either a b
Left forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack
forall a b. (a -> b) -> a -> b
$ String
"invalid padding at offset: "
forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (Ptr Word64
p forall a b. Ptr a -> Ptr b -> Int
`minusPtr` Ptr Word64
sptr)
look :: Ptr Word8 -> IO Word64
look :: Ptr Word8 -> IO Word64
look !Ptr Word8
p = forall {a}. Integral a => a -> Word64
lix forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Word64
w64 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Storable a => Ptr a -> IO a
peek @Word8 Ptr Word8
p
go :: Ptr Word8 -> Ptr Word64 -> IO (Either Text ByteString)
go !Ptr Word8
dst !Ptr Word64
src
| forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
8 forall a. Ord a => a -> a -> Bool
>= Ptr Word8
end = do
let src' :: Ptr b
src' = forall a b. Ptr a -> Ptr b
castPtr Ptr Word64
src
Word64
a <- Ptr Word8 -> IO Word64
look forall {b}. Ptr b
src'
Word64
b <- Ptr Word8 -> IO Word64
look (forall a b. Ptr a -> Int -> Ptr b
plusPtr forall {b}. Ptr b
src' Int
1)
Word64
c <- Ptr Word8 -> IO Word64
look (forall a b. Ptr a -> Int -> Ptr b
plusPtr forall {b}. Ptr b
src' Int
2)
Word64
d <- Ptr Word8 -> IO Word64
look (forall a b. Ptr a -> Int -> Ptr b
plusPtr forall {b}. Ptr b
src' Int
3)
Word64
e <- Ptr Word8 -> IO Word64
look (forall a b. Ptr a -> Int -> Ptr b
plusPtr forall {b}. Ptr b
src' Int
4)
Word64
f <- Ptr Word8 -> IO Word64
look (forall a b. Ptr a -> Int -> Ptr b
plusPtr forall {b}. Ptr b
src' Int
5)
Word64
g <- Ptr Word8 -> IO Word64
look (forall a b. Ptr a -> Int -> Ptr b
plusPtr forall {b}. Ptr b
src' Int
6)
Word64
h <- Ptr Word8 -> IO Word64
look (forall a b. Ptr a -> Int -> Ptr b
plusPtr forall {b}. Ptr b
src' Int
7)
forall {a} {a} {a} {a} {a} {a} {a} {a}.
(Integral a, Integral a, Integral a, Integral a, Integral a,
Integral a, Integral a, Integral a) =>
Ptr Word8
-> Ptr Word64
-> a
-> a
-> a
-> a
-> a
-> a
-> a
-> a
-> IO (Either Text ByteString)
finalChunk Ptr Word8
dst Ptr Word64
src Word64
a Word64
b Word64
c Word64
d Word64
e Word64
f Word64
g Word64
h
| Bool
otherwise = do
!Word64
t <- Ptr Word64 -> IO Word64
peekWord64BE Ptr Word64
src
let a :: Word64
a = forall {a}. Integral a => a -> Word64
lix (forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
t Int
56)
b :: Word64
b = forall {a}. Integral a => a -> Word64
lix (forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
t Int
48)
c :: Word64
c = forall {a}. Integral a => a -> Word64
lix (forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
t Int
40)
d :: Word64
d = forall {a}. Integral a => a -> Word64
lix (forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
t Int
32)
e :: Word64
e = forall {a}. Integral a => a -> Word64
lix (forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
t Int
24)
f :: Word64
f = forall {a}. Integral a => a -> Word64
lix (forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
t Int
16)
g :: Word64
g = forall {a}. Integral a => a -> Word64
lix (forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
t Int
8)
h :: Word64
h = forall {a}. Integral a => a -> Word64
lix Word64
t
Ptr Word8
-> Ptr Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> IO (Either Text ByteString)
decodeChunk Ptr Word8
dst Ptr Word64
src Word64
a Word64
b Word64
c Word64
d Word64
e Word64
f Word64
g Word64
h
finalChunk :: Ptr Word8
-> Ptr Word64
-> a
-> a
-> a
-> a
-> a
-> a
-> a
-> a
-> IO (Either Text ByteString)
finalChunk !Ptr Word8
dst !Ptr Word64
src !a
a !a
b !a
c !a
d !a
e !a
f !a
g !a
h
| a
a forall a. Eq a => a -> a -> Bool
== a
0x63 = Ptr Word64 -> IO (Either Text ByteString)
padErr Ptr Word64
src
| a
b forall a. Eq a => a -> a -> Bool
== a
0x63 = Ptr Word64 -> IO (Either Text ByteString)
padErr (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
1)
| a
a forall a. Eq a => a -> a -> Bool
== a
0xff = Ptr Word64 -> IO (Either Text ByteString)
err Ptr Word64
src
| a
b forall a. Eq a => a -> a -> Bool
== a
0xff = Ptr Word64 -> IO (Either Text ByteString)
err (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
1)
| a
c forall a. Eq a => a -> a -> Bool
== a
0xff = Ptr Word64 -> IO (Either Text ByteString)
err (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
2)
| a
d forall a. Eq a => a -> a -> Bool
== a
0xff = Ptr Word64 -> IO (Either Text ByteString)
err (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
3)
| a
e forall a. Eq a => a -> a -> Bool
== a
0xff = Ptr Word64 -> IO (Either Text ByteString)
err (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
4)
| a
f forall a. Eq a => a -> a -> Bool
== a
0xff = Ptr Word64 -> IO (Either Text ByteString)
err (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
5)
| a
g forall a. Eq a => a -> a -> Bool
== a
0xff = Ptr Word64 -> IO (Either Text ByteString)
err (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
6)
| a
h forall a. Eq a => a -> a -> Bool
== a
0xff = Ptr Word64 -> IO (Either Text ByteString)
err (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
7)
| Bool
otherwise = do
let !o1 :: Word8
o1 = (forall a b. (Integral a, Num b) => a -> b
fromIntegral a
a forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
3) forall a. Bits a => a -> a -> a
.|. (forall a b. (Integral a, Num b) => a -> b
fromIntegral a
b forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
2)
!o2 :: Word8
o2 = (forall a b. (Integral a, Num b) => a -> b
fromIntegral a
b forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
6)
forall a. Bits a => a -> a -> a
.|. (forall a b. (Integral a, Num b) => a -> b
fromIntegral a
c forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
1)
forall a. Bits a => a -> a -> a
.|. (forall a b. (Integral a, Num b) => a -> b
fromIntegral a
d forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
4)
!o3 :: Word8
o3 = (forall a b. (Integral a, Num b) => a -> b
fromIntegral a
d forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
4) forall a. Bits a => a -> a -> a
.|. (forall a b. (Integral a, Num b) => a -> b
fromIntegral a
e forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
1)
!o4 :: Word8
o4 = (forall a b. (Integral a, Num b) => a -> b
fromIntegral a
e forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
7)
forall a. Bits a => a -> a -> a
.|. (forall a b. (Integral a, Num b) => a -> b
fromIntegral a
f forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
2)
forall a. Bits a => a -> a -> a
.|. (forall a b. (Integral a, Num b) => a -> b
fromIntegral a
g forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
3)
!o5 :: Word8
o5 = (forall a b. (Integral a, Num b) => a -> b
fromIntegral a
g forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
5) forall a. Bits a => a -> a -> a
.|. forall a b. (Integral a, Num b) => a -> b
fromIntegral a
h
forall a. Storable a => Ptr a -> a -> IO ()
poke @Word8 Ptr Word8
dst Word8
o1
forall a. Storable a => Ptr a -> a -> IO ()
poke @Word8 (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
dst Int
1) Word8
o2
case (a
c,a
d,a
e,a
f,a
g,a
h) of
(a
0x63,a
0x63,a
0x63,a
0x63,a
0x63,a
0x63) ->
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. b -> Either a b
Right (ForeignPtr Word8 -> Int -> Int -> ByteString
PS ForeignPtr Word8
dfp Int
0 (Int
1 forall a. Num a => a -> a -> a
+ forall a b. Ptr a -> Ptr b -> Int
minusPtr Ptr Word8
dst Ptr Word8
dptr)))
(a
0x63,a
_,a
_,a
_,a
_,a
_) -> Ptr Word64 -> IO (Either Text ByteString)
padErr (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
3)
(a
_,a
0x63,a
0x63,a
0x63,a
0x63,a
0x63) -> Ptr Word64 -> IO (Either Text ByteString)
padErr (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
3)
(a
_,a
0x63,a
_,a
_,a
_,a
_) -> Ptr Word64 -> IO (Either Text ByteString)
padErr (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
4)
(a
_,a
_,a
0x63,a
0x63,a
0x63,a
0x63) -> do
forall a. Storable a => Ptr a -> a -> IO ()
poke @Word8 (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
dst Int
2) Word8
o3
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. b -> Either a b
Right (ForeignPtr Word8 -> Int -> Int -> ByteString
PS ForeignPtr Word8
dfp Int
0 (Int
2 forall a. Num a => a -> a -> a
+ forall a b. Ptr a -> Ptr b -> Int
minusPtr Ptr Word8
dst Ptr Word8
dptr)))
(a
_,a
_,a
0x63,a
_,a
_,a
_) -> Ptr Word64 -> IO (Either Text ByteString)
padErr (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
5)
(a
_,a
_,a
_,a
0x63,a
0x63,a
0x63) -> do
forall a. Storable a => Ptr a -> a -> IO ()
poke @Word8 (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
dst Int
2) Word8
o3
forall a. Storable a => Ptr a -> a -> IO ()
poke @Word8 (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
dst Int
3) Word8
o4
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. b -> Either a b
Right (ForeignPtr Word8 -> Int -> Int -> ByteString
PS ForeignPtr Word8
dfp Int
0 (Int
3 forall a. Num a => a -> a -> a
+ forall a b. Ptr a -> Ptr b -> Int
minusPtr Ptr Word8
dst Ptr Word8
dptr)))
(a
_,a
_,a
_,a
0x63,a
_,a
_) -> Ptr Word64 -> IO (Either Text ByteString)
padErr (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
6)
(a
_,a
_,a
_,a
_,a
0x63,a
0x63) -> Ptr Word64 -> IO (Either Text ByteString)
padErr (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
6)
(a
_,a
_,a
_,a
_,a
0x63,a
_) -> Ptr Word64 -> IO (Either Text ByteString)
padErr (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
7)
(a
_,a
_,a
_,a
_,a
_,a
0x63) -> do
forall a. Storable a => Ptr a -> a -> IO ()
poke @Word8 (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
dst Int
2) Word8
o3
forall a. Storable a => Ptr a -> a -> IO ()
poke @Word8 (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
dst Int
3) Word8
o4
forall a. Storable a => Ptr a -> a -> IO ()
poke @Word8 (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
dst Int
4) Word8
o5
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. b -> Either a b
Right (ForeignPtr Word8 -> Int -> Int -> ByteString
PS ForeignPtr Word8
dfp Int
0 (Int
4 forall a. Num a => a -> a -> a
+ forall a b. Ptr a -> Ptr b -> Int
minusPtr Ptr Word8
dst Ptr Word8
dptr)))
(a
_,a
_,a
_,a
_,a
_,a
_) -> do
forall a. Storable a => Ptr a -> a -> IO ()
poke @Word8 (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
dst Int
2) Word8
o3
forall a. Storable a => Ptr a -> a -> IO ()
poke @Word8 (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
dst Int
3) Word8
o4
forall a. Storable a => Ptr a -> a -> IO ()
poke @Word8 (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
dst Int
4) Word8
o5
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. b -> Either a b
Right (ForeignPtr Word8 -> Int -> Int -> ByteString
PS ForeignPtr Word8
dfp Int
0 (Int
5 forall a. Num a => a -> a -> a
+ forall a b. Ptr a -> Ptr b -> Int
minusPtr Ptr Word8
dst Ptr Word8
dptr)))
decodeChunk :: Ptr Word8
-> Ptr Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> IO (Either Text ByteString)
decodeChunk !Ptr Word8
dst !Ptr Word64
src !Word64
a !Word64
b !Word64
c !Word64
d !Word64
e !Word64
f !Word64
g !Word64
h
| Word64
a forall a. Eq a => a -> a -> Bool
== Word64
0x63 = Ptr Word64 -> IO (Either Text ByteString)
padErr Ptr Word64
src
| Word64
b forall a. Eq a => a -> a -> Bool
== Word64
0x63 = Ptr Word64 -> IO (Either Text ByteString)
padErr (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
1)
| Word64
c forall a. Eq a => a -> a -> Bool
== Word64
0x63 = Ptr Word64 -> IO (Either Text ByteString)
padErr (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
2)
| Word64
d forall a. Eq a => a -> a -> Bool
== Word64
0x63 = Ptr Word64 -> IO (Either Text ByteString)
padErr (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
3)
| Word64
e forall a. Eq a => a -> a -> Bool
== Word64
0x63 = Ptr Word64 -> IO (Either Text ByteString)
padErr (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
4)
| Word64
f forall a. Eq a => a -> a -> Bool
== Word64
0x63 = Ptr Word64 -> IO (Either Text ByteString)
padErr (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
5)
| Word64
g forall a. Eq a => a -> a -> Bool
== Word64
0x63 = Ptr Word64 -> IO (Either Text ByteString)
padErr (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
6)
| Word64
h forall a. Eq a => a -> a -> Bool
== Word64
0x63 = Ptr Word64 -> IO (Either Text ByteString)
padErr (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
7)
| Word64
a forall a. Eq a => a -> a -> Bool
== Word64
0xff = Ptr Word64 -> IO (Either Text ByteString)
err Ptr Word64
src
| Word64
b forall a. Eq a => a -> a -> Bool
== Word64
0xff = Ptr Word64 -> IO (Either Text ByteString)
err (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
1)
| Word64
c forall a. Eq a => a -> a -> Bool
== Word64
0xff = Ptr Word64 -> IO (Either Text ByteString)
err (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
2)
| Word64
d forall a. Eq a => a -> a -> Bool
== Word64
0xff = Ptr Word64 -> IO (Either Text ByteString)
err (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
3)
| Word64
e forall a. Eq a => a -> a -> Bool
== Word64
0xff = Ptr Word64 -> IO (Either Text ByteString)
err (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
4)
| Word64
f forall a. Eq a => a -> a -> Bool
== Word64
0xff = Ptr Word64 -> IO (Either Text ByteString)
err (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
5)
| Word64
g forall a. Eq a => a -> a -> Bool
== Word64
0xff = Ptr Word64 -> IO (Either Text ByteString)
err (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
6)
| Word64
h forall a. Eq a => a -> a -> Bool
== Word64
0xff = Ptr Word64 -> IO (Either Text ByteString)
err (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
7)
| Bool
otherwise = do
let !w :: Word64
w = (forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
a Int
35
forall a. Bits a => a -> a -> a
.|. forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
b Int
30
forall a. Bits a => a -> a -> a
.|. forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
c Int
25
forall a. Bits a => a -> a -> a
.|. forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
d Int
20
forall a. Bits a => a -> a -> a
.|. forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
e Int
15
forall a. Bits a => a -> a -> a
.|. forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
f Int
10
forall a. Bits a => a -> a -> a
.|. forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
g Int
5
forall a. Bits a => a -> a -> a
.|. Word64
h) :: Word64
forall a. Storable a => Ptr a -> a -> IO ()
poke @Word32 (forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
dst) (Word32 -> Word32
byteSwap32 (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
w Int
8)))
forall a. Storable a => Ptr a -> a -> IO ()
poke @Word8 (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
dst Int
4) (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
w)
Ptr Word8 -> Ptr Word64 -> IO (Either Text ByteString)
go (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
dst Int
5) (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
8)