{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE TypeApplications #-}
module Data.ByteString.Base64.Internal.W64.Loop
( innerLoop
, decodeLoop
, lenientLoop
) where
import Data.Bits
import Data.ByteString.Internal
import Data.ByteString.Base64.Internal.Utils
import qualified Data.ByteString.Base64.Internal.W16.Loop as W16
import Data.Text (Text)
import Foreign.ForeignPtr
import Foreign.Ptr
import Foreign.Storable
import GHC.Word
innerLoop
    :: Ptr Word16
    -> Ptr Word64
    -> Ptr Word64
    -> Ptr Word64
    -> (Ptr Word8 -> Ptr Word8 -> IO ByteString)
    -> IO ByteString
innerLoop :: Ptr Word16
-> Ptr Word64
-> Ptr Word64
-> Ptr Word64
-> (Ptr Word8 -> Ptr Word8 -> IO ByteString)
-> IO ByteString
innerLoop !Ptr Word16
etable !Ptr Word64
sptr !Ptr Word64
dptr !Ptr Word64
end Ptr Word8 -> Ptr Word8 -> IO ByteString
finish = Ptr Word64 -> Ptr Word64 -> IO ByteString
forall b.
(Storable b, Num b) =>
Ptr Word64 -> Ptr b -> IO ByteString
go Ptr Word64
sptr Ptr Word64
dptr
  where
    go :: Ptr Word64 -> Ptr b -> IO ByteString
go !Ptr Word64
src !Ptr b
dst
      | Ptr Word64 -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
7 Ptr Word64 -> Ptr Word64 -> Bool
forall a. Ord a => a -> a -> Bool
>= Ptr Word64
end =
        Ptr Word16
-> Ptr Word8
-> Ptr Word16
-> Ptr Word8
-> (Ptr Word8 -> Ptr Word8 -> IO ByteString)
-> IO ByteString
W16.innerLoop Ptr Word16
etable (Ptr Word64 -> Ptr Word8
forall a b. Ptr a -> Ptr b
castPtr Ptr Word64
src) (Ptr b -> Ptr Word16
forall a b. Ptr a -> Ptr b
castPtr Ptr b
dst) (Ptr Word64 -> Ptr Word8
forall a b. Ptr a -> Ptr b
castPtr Ptr Word64
end) Ptr Word8 -> Ptr Word8 -> IO ByteString
finish
      | Bool
otherwise = do
        !Word64
t <- Ptr Word64 -> IO Word64
peekWord64BE Ptr Word64
src
        let !a :: Word64
a = (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
t Int
52) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. Word64
0xfff
            !b :: Word64
b = (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
t Int
40) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. Word64
0xfff
            !c :: Word64
c = (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
t Int
28) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. Word64
0xfff
            !d :: Word64
d = (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
t Int
16) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. Word64
0xfff
        !Word64
w <- Word16 -> Word64
w64_16 (Word16 -> Word64) -> IO Word16 -> IO Word64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word16 -> Int -> IO Word16
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr Word16
etable (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
a)
        !Word64
x <- Word16 -> Word64
w64_16 (Word16 -> Word64) -> IO Word16 -> IO Word64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word16 -> Int -> IO Word16
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr Word16
etable (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
b)
        !Word64
y <- Word16 -> Word64
w64_16 (Word16 -> Word64) -> IO Word16 -> IO Word64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word16 -> Int -> IO Word16
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr Word16
etable (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
c)
        !Word64
z <- Word16 -> Word64
w64_16 (Word16 -> Word64) -> IO Word16 -> IO Word64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word16 -> Int -> IO Word16
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr Word16
etable (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
d)
        let !xx :: Word64
xx = 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 Int
16)
               Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|. (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
y Int
32)
               Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|. (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
z Int
48)
        Ptr b -> b -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr b
dst (Word64 -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
xx)
        Ptr Word64 -> Ptr b -> IO ByteString
go (Ptr Word64 -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word64
src Int
6) (Ptr b -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr b
dst Int
8)
{-# inline innerLoop #-}
decodeLoop
    :: Ptr Word8
        
    -> Ptr Word8
        
    -> Ptr Word8
        
    -> Ptr Word8
        
    -> ForeignPtr Word8
        
    -> IO (Either Text ByteString)
decodeLoop :: Ptr Word8
-> Ptr Word8
-> Ptr Word8
-> Ptr Word8
-> ForeignPtr Word8
-> IO (Either Text ByteString)
decodeLoop = Ptr Word8
-> Ptr Word8
-> Ptr Word8
-> Ptr Word8
-> ForeignPtr Word8
-> IO (Either Text ByteString)
W16.decodeLoop
{-# inline decodeLoop #-}
lenientLoop
    :: Ptr Word8
        
    -> Ptr Word8
        
    -> Ptr Word8
        
    -> Ptr Word8
        
    -> ForeignPtr Word8
        
    -> IO ByteString
lenientLoop :: Ptr Word8
-> Ptr Word8
-> Ptr Word8
-> Ptr Word8
-> ForeignPtr Word8
-> IO ByteString
lenientLoop = Ptr Word8
-> Ptr Word8
-> Ptr Word8
-> Ptr Word8
-> ForeignPtr Word8
-> IO ByteString
W16.lenientLoop