{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif

-- |
-- Module      : Data.ByteString.Base64.URL
-- Copyright   : (c) 2012 Deian Stefan
--
-- License     : BSD-style
-- Maintainer  : deian@cs.stanford.edu
-- Stability   : experimental
-- Portability : GHC
--
-- Fast and efficient encoding and decoding of base64url-encoded strings.
--
-- @since 0.1.1.0
module Data.ByteString.Base64.URL
  ( encode
  , encodeUnpadded
  , decode
  , decodePadded
  , decodeUnpadded
  , decodeLenient
  ) 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 a string into base64url form.  The result will always be a
-- multiple of 4 bytes in length.
encode :: ByteString -> ByteString
encode :: ByteString -> ByteString
encode = Padding -> EncodeTable -> ByteString -> ByteString
encodeWith Padding
Padded (ByteString -> EncodeTable
mkEncodeTable ByteString
alphabet)

-- | Encode a string into unpadded base64url form.
--
-- @since 1.1.0.0
encodeUnpadded :: ByteString -> ByteString
encodeUnpadded :: ByteString -> ByteString
encodeUnpadded = Padding -> EncodeTable -> ByteString -> ByteString
encodeWith Padding
Unpadded (ByteString -> EncodeTable
mkEncodeTable ByteString
alphabet)

-- | Decode a base64url-encoded string applying padding if necessary.
-- This function follows the specification in <http://tools.ietf.org/rfc/rfc4648 RFC 4648>
-- and in <https://tools.ietf.org/html/rfc7049#section-2.4.4.2 RFC 7049 2.4>
decode :: ByteString -> Either String ByteString
decode :: ByteString -> Either String ByteString
decode = Padding
-> ForeignPtr Word8 -> ByteString -> Either String ByteString
decodeWithTable Padding
Don'tCare ForeignPtr Word8
decodeFP

-- | Decode a padded base64url-encoded string, failing if input is improperly padded.
-- This function follows the specification in <http://tools.ietf.org/rfc/rfc4648 RFC 4648>
-- and in <https://tools.ietf.org/html/rfc7049#section-2.4.4.2 RFC 7049 2.4>
--
-- @since 1.1.0.0
decodePadded :: ByteString -> Either String ByteString
decodePadded :: ByteString -> Either String ByteString
decodePadded = Padding
-> ForeignPtr Word8 -> ByteString -> Either String ByteString
decodeWithTable Padding
Padded ForeignPtr Word8
decodeFP

-- | Decode a unpadded base64url-encoded string, failing if input is padded.
-- This function follows the specification in <http://tools.ietf.org/rfc/rfc4648 RFC 4648>
-- and in <https://tools.ietf.org/html/rfc7049#section-2.4.4.2 RFC 7049 2.4>
--
-- @since 1.1.0.0
decodeUnpadded :: ByteString -> Either String ByteString
decodeUnpadded :: ByteString -> Either String ByteString
decodeUnpadded = Padding
-> ForeignPtr Word8 -> ByteString -> Either String ByteString
decodeWithTable Padding
Unpadded ForeignPtr Word8
decodeFP

-- | Decode a base64url-encoded string.  This function is lenient in
-- following the specification from
-- <http://tools.ietf.org/rfc/rfc4648 RFC 4648>, and will not
-- generate parse errors no matter how poor its input.
decodeLenient :: ByteString -> ByteString
decodeLenient :: ByteString -> ByteString
decodeLenient = ForeignPtr Word8 -> ByteString -> ByteString
decodeLenientWithTable ForeignPtr Word8
decodeFP


alphabet :: ByteString
alphabet :: ByteString
alphabet = [Word8] -> ByteString
B.pack ([Word8] -> ByteString) -> [Word8] -> ByteString
forall a b. (a -> b) -> a -> b
$ [Word8
65..Word8
90] [Word8] -> [Word8] -> [Word8]
forall a. [a] -> [a] -> [a]
++ [Word8
97..Word8
122] [Word8] -> [Word8] -> [Word8]
forall a. [a] -> [a] -> [a]
++ [Word8
48..Word8
57] [Word8] -> [Word8] -> [Word8]
forall a. [a] -> [a] -> [a]
++ [Word8
45,Word8
95]
{-# NOINLINE alphabet #-}

decodeFP :: ForeignPtr Word8
PS ForeignPtr Word8
decodeFP Int
_ Int
_ = [Word8] -> ByteString
B.pack ([Word8] -> ByteString) -> [Word8] -> ByteString
forall a b. (a -> b) -> a -> b
$ Int -> Word8 -> [Word8]
forall a. Int -> a -> [a]
replicate Int
45 Word8
forall a. Integral a => a
x [Word8] -> [Word8] -> [Word8]
forall a. [a] -> [a] -> [a]
++ [Word8
62,Word8
forall a. Integral a => a
x,Word8
forall a. Integral a => a
x] [Word8] -> [Word8] -> [Word8]
forall a. [a] -> [a] -> [a]
++ [Word8
52..Word8
61] [Word8] -> [Word8] -> [Word8]
forall a. [a] -> [a] -> [a]
++ [Word8
forall a. Integral a => a
x,Word8
forall a. Integral a => a
x,
  Word8
forall a. Integral a => a
x,Word8
forall a. Integral a => a
done,Word8
forall a. Integral a => a
x,Word8
forall a. Integral a => a
x,Word8
forall a. Integral a => a
x] [Word8] -> [Word8] -> [Word8]
forall a. [a] -> [a] -> [a]
++ [Word8
0..Word8
25] [Word8] -> [Word8] -> [Word8]
forall a. [a] -> [a] -> [a]
++ [Word8
forall a. Integral a => a
x,Word8
forall a. Integral a => a
x,Word8
forall a. Integral a => a
x,Word8
forall a. Integral a => a
x,Word8
63,Word8
forall a. Integral a => a
x] [Word8] -> [Word8] -> [Word8]
forall a. [a] -> [a] -> [a]
++ [Word8
26..Word8
51] [Word8] -> [Word8] -> [Word8]
forall a. [a] -> [a] -> [a]
++ Int -> Word8 -> [Word8]
forall a. Int -> a -> [a]
replicate Int
133 Word8
forall a. Integral a => a
x
{-# NOINLINE decodeFP #-}

x :: Integral a => a
x :: a
x = a
255
{-# INLINE x #-}