{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif
module Data.ByteString.Base64
    (
      encode
    , decode
    , decodeLenient
    , joinWith
    ) where
import Data.ByteString.Base64.Internal
import qualified Data.ByteString as B
import Data.ByteString.Internal (ByteString(..))
import Data.Word (Word8)
import Foreign.ForeignPtr (ForeignPtr)
encode :: ByteString -> ByteString
encode s = encodeWith (mkEncodeTable alphabet) s
decode :: ByteString -> Either String ByteString
decode s = decodeWithTable decodeFP s
decodeLenient :: ByteString -> ByteString
decodeLenient s = decodeLenientWithTable decodeFP s
alphabet :: ByteString
alphabet = B.pack $ [65..90] ++ [97..122] ++ [48..57] ++ [43,47]
{-# NOINLINE alphabet #-}
decodeFP :: ForeignPtr Word8
PS decodeFP _ _ = B.pack $
  replicate 43 x ++ [62,x,x,x,63] ++ [52..61] ++ [x,x,x,done,x,x,x] ++
  [0..25] ++ [x,x,x,x,x,x] ++ [26..51] ++ replicate 133 x
{-# NOINLINE decodeFP #-}
x :: Integral a => a
x = 255
{-# INLINE x #-}