{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
module Data.ByteString.Base32.Internal
( encodeBase32_
, encodeBase32NoPad_
, decodeBase32_
, validateBase32
, validateLastNPads
) where
import qualified Data.ByteString as BS
import Data.ByteString.Internal
import Data.ByteString.Base32.Internal.Head
import Data.Text (Text)
import Foreign.ForeignPtr
import Foreign.Ptr
import Foreign.Storable
import GHC.Word
import System.IO.Unsafe
validateBase32 :: ByteString -> ByteString -> Bool
validateBase32 :: ByteString -> ByteString -> Bool
validateBase32 !ByteString
alphabet bs :: ByteString
bs@(PS ForeignPtr Word8
_ Int
_ Int
l)
| Int
l forall a. Eq a => a -> a -> Bool
== Int
0 = Bool
True
| Int
r forall a. Eq a => a -> a -> Bool
== Int
0 = ByteString -> Bool
f ByteString
bs
| Int
r forall a. Eq a => a -> a -> Bool
== Int
2 = ByteString -> Bool
f (ByteString -> ByteString -> ByteString
BS.append ByteString
bs ByteString
"======")
| Int
r forall a. Eq a => a -> a -> Bool
== Int
4 = ByteString -> Bool
f (ByteString -> ByteString -> ByteString
BS.append ByteString
bs ByteString
"====")
| Int
r forall a. Eq a => a -> a -> Bool
== Int
5 = ByteString -> Bool
f (ByteString -> ByteString -> ByteString
BS.append ByteString
bs ByteString
"===")
| Int
r forall a. Eq a => a -> a -> Bool
== Int
7 = ByteString -> Bool
f (ByteString -> ByteString -> ByteString
BS.append ByteString
bs ByteString
"=")
| Bool
otherwise = Bool
False
where
r :: Int
r = Int
l forall a. Integral a => a -> a -> a
`rem` Int
8
f :: ByteString -> Bool
f (PS ForeignPtr Word8
fp Int
o Int
l') = forall a. IO a -> a
accursedUnutterablePerformIO forall a b. (a -> b) -> a -> b
$ 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 -> Ptr Word8 -> IO Bool
go (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
p Int
o) (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
p (Int
l' forall a. Num a => a -> a -> a
+ Int
o))
go :: Ptr Word8 -> Ptr Word8 -> IO Bool
go !Ptr Word8
p !Ptr Word8
end
| Ptr Word8
p forall a. Eq a => a -> a -> Bool
== Ptr Word8
end = forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
| Bool
otherwise = do
Word8
w <- forall a. Storable a => Ptr a -> IO a
peek Ptr Word8
p
let check :: Word8 -> Bool
check Word8
a
| Word8
a forall a. Eq a => a -> a -> Bool
== Word8
0x3d, forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
p Int
1 forall a. Eq a => a -> a -> Bool
== Ptr Word8
end = Bool
True
| Word8
a forall a. Eq a => a -> a -> Bool
== Word8
0x3d, forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
p Int
2 forall a. Eq a => a -> a -> Bool
== Ptr Word8
end = Bool
True
| Word8
a forall a. Eq a => a -> a -> Bool
== Word8
0x3d, forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
p Int
3 forall a. Eq a => a -> a -> Bool
== Ptr Word8
end = Bool
True
| Word8
a forall a. Eq a => a -> a -> Bool
== Word8
0x3d, forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
p Int
4 forall a. Eq a => a -> a -> Bool
== Ptr Word8
end = Bool
True
| Word8
a forall a. Eq a => a -> a -> Bool
== Word8
0x3d, forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
p Int
5 forall a. Eq a => a -> a -> Bool
== Ptr Word8
end = Bool
True
| Word8
a forall a. Eq a => a -> a -> Bool
== Word8
0x3d, forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
p Int
6 forall a. Eq a => a -> a -> Bool
== Ptr Word8
end = Bool
True
| Word8
a forall a. Eq a => a -> a -> Bool
== Word8
0x3d = Bool
False
| Bool
otherwise = Word8 -> ByteString -> Bool
BS.elem Word8
a ByteString
alphabet
if Word8 -> Bool
check Word8
w then Ptr Word8 -> Ptr Word8 -> IO Bool
go (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
p Int
1) Ptr Word8
end else forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
{-# INLINE validateBase32 #-}
validateLastNPads
:: Int
-> ByteString
-> IO (Either Text ByteString)
-> Either Text ByteString
validateLastNPads :: Int
-> ByteString
-> IO (Either Text ByteString)
-> Either Text ByteString
validateLastNPads !Int
n (PS !ForeignPtr Word8
fp !Int
o !Int
l) IO (Either Text ByteString)
io
| Bool -> Bool
not Bool
valid = forall a b. a -> Either a b
Left Text
"Base32-encoded bytestring has invalid padding"
| Bool
otherwise = forall a. IO a -> a
unsafeDupablePerformIO IO (Either Text ByteString)
io
where
!lo :: Int
lo = Int
l forall a. Num a => a -> a -> a
+ Int
o
valid :: Bool
valid = forall a. IO a -> a
accursedUnutterablePerformIO forall a b. (a -> b) -> a -> b
$ 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 -> do
let end :: Ptr b
end = forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
p Int
lo
let go :: Ptr Word8 -> IO Bool
go :: Ptr Word8 -> IO Bool
go !Ptr Word8
q
| Ptr Word8
q forall a. Eq a => a -> a -> Bool
== forall {b}. Ptr b
end = forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
| Bool
otherwise = do
Word8
a <- forall a. Storable a => Ptr a -> IO a
peek Ptr Word8
q
if Word8
a forall a. Eq a => a -> a -> Bool
== Word8
0x3d then forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False else Ptr Word8 -> IO Bool
go (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
q Int
1)
Ptr Word8 -> IO Bool
go (forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
p (Int
lo forall a. Num a => a -> a -> a
- Int
n))
{-# INLINE validateLastNPads #-}