{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
module Data.ByteString.Base32.Internal
( validateBase32
) where
import qualified Data.ByteString as BS
import Data.ByteString.Internal
import Foreign.ForeignPtr
import Foreign.Ptr
import Foreign.Storable
validateBase32 :: ByteString -> ByteString -> Bool
validateBase32 !alphabet (PS fp off l) =
accursedUnutterablePerformIO $ withForeignPtr fp $ \p ->
go (plusPtr p off) (plusPtr p (l + off))
where
go !p !end
| p == end = return True
| otherwise = do
w <- peek p
let f a
| a == 0x3d, plusPtr p 1 == end = True
| a == 0x3d, plusPtr p 2 == end = True
| a == 0x3d, plusPtr p 3 == end = True
| a == 0x3d, plusPtr p 4 == end = True
| a == 0x3d, plusPtr p 5 == end = True
| a == 0x3d, plusPtr p 6 == end = True
| a == 0x3d = False
| otherwise = BS.elem a alphabet
if f w then go (plusPtr p 1) end else return False
{-# INLINE validateBase32 #-}