{-# LANGUAGE DataKinds #-}
-- |
-- Module       : Data.Text.Lazy.Encoding.Base64.URL
-- Copyright    : (c) 2019-2023 Emily Pillmore
-- License      : BSD-style
--
-- Maintainer   : Emily Pillmore <emilypi@cohomolo.gy>
-- Stability    : stable
-- Portability  : non-portable
--
-- This module contains 'Data.Text.Lazy.Text'-valued combinators for
-- implementing the RFC 4648 specification of the Base64url
-- encoding format. This includes strictly padded/unpadded and lenient decoding
-- variants, as well as internal and external validation for canonicity.
--
module Data.Text.Lazy.Encoding.Base64.URL
( -- * Encoding
  encodeBase64
, encodeBase64Unpadded
  -- * Decoding
, decodeBase64
, decodeBase64Untyped
, decodeBase64UntypedWith
, decodeBase64Unpadded
, decodeBase64UnpaddedUntyped
, decodeBase64UnpaddedUntypedWith
, decodeBase64Padded
, decodeBase64PaddedUntyped
, decodeBase64PaddedUntypedWith
, decodeBase64Lenient
  -- * Validation
, isBase64Url
, isValidBase64Url
) where

import Data.Base64.Types

import Data.Bifunctor (first)
import Data.ByteString.Lazy (ByteString)
import qualified Data.ByteString.Lazy.Base64.URL as BL64U

import qualified Data.Text as T
import Data.Text.Encoding.Base64.Error
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL



-- $setup
--
-- >>> import Data.Base64.Types
-- >>> :set -XOverloadedStrings
-- >>> :set -XTypeApplications
-- >>> :set -XDataKinds
--

-- | Encode a 'TL.Text' value in Base64url with padding.
--
-- See: <https://tools.ietf.org/html/rfc4648#section-5 RFC-4648 section 5>
--
-- === __Examples__:
--
-- >>> encodeBase64 "<<?>>"
-- "PDw_Pj4="
--
encodeBase64 :: TL.Text -> Base64 'UrlPadded TL.Text
encodeBase64 :: Text -> Base64 'UrlPadded Text
encodeBase64 = ByteString -> Base64 'UrlPadded Text
BL64U.encodeBase64 (ByteString -> Base64 'UrlPadded Text)
-> (Text -> ByteString) -> Text -> Base64 'UrlPadded Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
TL.encodeUtf8
{-# INLINE encodeBase64 #-}

-- | Decode an arbitrarily Base64url-encoded 'TL.Text' value.
--
-- For typed values:
--   - If a padded value is required, use 'decodeBase64Padded'
--   - If an unpadded value is required, use 'decodeBase64Unpadded'
--
-- See: <https://tools.ietf.org/html/rfc4648#section-4 RFC-4648 section 4>
--
-- === __Examples__:
--
-- >>> decodeBase64 $ assertBase64 @'UrlPadded "PDw_Pj4="
-- "<<?>>"
--
-- >>> decodeBase64 $ assertBase64 @'UrlUnpadded "PDw_Pj4"
-- "<<?>>"
--
decodeBase64 :: UrlAlphabet k => Base64 k TL.Text -> TL.Text
decodeBase64 :: forall (k :: Alphabet). UrlAlphabet k => Base64 k Text -> Text
decodeBase64 = ByteString -> Text
TL.decodeUtf8 (ByteString -> Text)
-> (Base64 k Text -> ByteString) -> Base64 k Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Base64 k ByteString -> ByteString
forall (k :: Alphabet).
UrlAlphabet k =>
Base64 k ByteString -> ByteString
BL64U.decodeBase64 (Base64 k ByteString -> ByteString)
-> (Base64 k Text -> Base64 k ByteString)
-> Base64 k Text
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> ByteString) -> Base64 k Text -> Base64 k ByteString
forall a b. (a -> b) -> Base64 k a -> Base64 k b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ByteString
TL.encodeUtf8
{-# INLINE decodeBase64 #-}

-- | Decode an untyped Base64url-encoded 'TL.Text' value. If its length is not a multiple
-- of 4, then padding chars will be added to fill out the input to a multiple of
-- 4 for safe decoding as base64url encodings are optionally padded.
--
-- For a decoder that fails on unpadded input, use 'decodeBase64Unpadded'.
--
-- See: <https://tools.ietf.org/html/rfc4648#section-4 RFC-4648 section 4>
--
-- === __Examples__:
--
-- >>> decodeBase64Untyped "PDw_Pj4="
-- Right "<<?>>"
--
-- >>> decodeBase64Untyped "PDw_Pj4"
-- Right "<<?>>"
--
-- >>> decodeBase64Untyped "PDw-Pg="
-- Left "Base64-encoded bytestring has invalid padding"
--
-- >>> decodeBase64Untyped "PDw-Pg"
-- Right "<<>>"
--
decodeBase64Untyped :: TL.Text -> Either T.Text TL.Text
decodeBase64Untyped :: Text -> Either Text Text
decodeBase64Untyped = (ByteString -> Text) -> Either Text ByteString -> Either Text Text
forall a b. (a -> b) -> Either Text a -> Either Text b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Text
TL.decodeUtf8
  (Either Text ByteString -> Either Text Text)
-> (Text -> Either Text ByteString) -> Text -> Either Text Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either Text ByteString
BL64U.decodeBase64Untyped
  (ByteString -> Either Text ByteString)
-> (Text -> ByteString) -> Text -> Either Text ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
TL.encodeUtf8
{-# INLINE decodeBase64Untyped #-}

-- | Attempt to decode an untyped lazy 'ByteString' value as Base64url, converting from
-- 'ByteString' to 'TL.Text' according to some encoding function. In practice,
-- This is something like 'decodeUtf8'', which may produce an error.
--
-- See: <https://tools.ietf.org/html/rfc4648#section-4 RFC-4648 section 4>
--
-- === __Examples__:
--
-- @
-- 'decodeBase64With' 'TL.decodeUtf8''
--   :: 'ByteString' -> 'Either' ('Base64Error' 'UnicodeException') 'TL.Text'
-- @
--
decodeBase64UntypedWith
    :: (ByteString -> Either err TL.Text)
      -- ^ convert a bytestring to text (e.g. 'TL.decodeUtf8'')
    -> ByteString
      -- ^ Input text to decode
    -> Either (Base64Error err) TL.Text
decodeBase64UntypedWith :: forall err.
(ByteString -> Either err Text)
-> ByteString -> Either (Base64Error err) Text
decodeBase64UntypedWith ByteString -> Either err Text
f ByteString
t = case ByteString -> Either Text ByteString
BL64U.decodeBase64Untyped ByteString
t of
  Left Text
de -> Base64Error err -> Either (Base64Error err) Text
forall a b. a -> Either a b
Left (Base64Error err -> Either (Base64Error err) Text)
-> Base64Error err -> Either (Base64Error err) Text
forall a b. (a -> b) -> a -> b
$ Text -> Base64Error err
forall e. Text -> Base64Error e
DecodeError Text
de
  Right ByteString
a -> (err -> Base64Error err)
-> Either err Text -> Either (Base64Error err) Text
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first err -> Base64Error err
forall e. e -> Base64Error e
ConversionError (ByteString -> Either err Text
f ByteString
a)
{-# INLINE decodeBase64UntypedWith #-}

-- | Encode a 'TL.Text' value in Base64url without padding. Note that for Base64url,
-- padding is optional. If you call this function, you will simply be encoding
-- as Base64url and stripping padding chars from the output.
--
-- See: <https://tools.ietf.org/html/rfc4648#section-3.2 RFC-4648 section 3.2>
--
-- === __Examples__:
--
-- >>> encodeBase64Unpadded "<<?>>"
-- "PDw_Pj4"
--
encodeBase64Unpadded :: TL.Text -> Base64 'UrlUnpadded TL.Text
encodeBase64Unpadded :: Text -> Base64 'UrlUnpadded Text
encodeBase64Unpadded = ByteString -> Base64 'UrlUnpadded Text
BL64U.encodeBase64Unpadded (ByteString -> Base64 'UrlUnpadded Text)
-> (Text -> ByteString) -> Text -> Base64 'UrlUnpadded Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
TL.encodeUtf8
{-# INLINE encodeBase64Unpadded #-}

-- | Decode an unpadded Base64url encoded 'Text' value.
--
-- See: <https://tools.ietf.org/html/rfc4648#section-4 RFC-4648 section 4>
--
-- === __Examples__:
--
-- >>> decodeBase64Unpadded $ assertBase64 @'UrlUnpadded "PDw_Pj4"
-- "<<?>>"
--
decodeBase64Unpadded :: Base64 'UrlUnpadded TL.Text -> TL.Text
decodeBase64Unpadded :: Base64 'UrlUnpadded Text -> Text
decodeBase64Unpadded = ByteString -> Text
TL.decodeUtf8
  (ByteString -> Text)
-> (Base64 'UrlUnpadded Text -> ByteString)
-> Base64 'UrlUnpadded Text
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Base64 'UrlUnpadded ByteString -> ByteString
BL64U.decodeBase64Unpadded
  (Base64 'UrlUnpadded ByteString -> ByteString)
-> (Base64 'UrlUnpadded Text -> Base64 'UrlUnpadded ByteString)
-> Base64 'UrlUnpadded Text
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> ByteString)
-> Base64 'UrlUnpadded Text -> Base64 'UrlUnpadded ByteString
forall a b.
(a -> b) -> Base64 'UrlUnpadded a -> Base64 'UrlUnpadded b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ByteString
TL.encodeUtf8
{-# INLINE decodeBase64Unpadded #-}

-- | Decode an unpadded, untyped Base64url encoded 'TL.Text' value.
--
-- See: <https://tools.ietf.org/html/rfc4648#section-4 RFC-4648 section 4>
--
-- === __Examples__:
--
-- >>> decodeBase64UnpaddedUntyped "PDw_Pj4"
-- Right "<<?>>"
--
-- >>> decodeBase64UnpaddedUntyped "PDw_Pj4="
-- Left "Base64-encoded bytestring has invalid padding"
--
decodeBase64UnpaddedUntyped :: TL.Text -> Either T.Text TL.Text
decodeBase64UnpaddedUntyped :: Text -> Either Text Text
decodeBase64UnpaddedUntyped = (ByteString -> Text) -> Either Text ByteString -> Either Text Text
forall a b. (a -> b) -> Either Text a -> Either Text b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Text
TL.decodeUtf8
    (Either Text ByteString -> Either Text Text)
-> (Text -> Either Text ByteString) -> Text -> Either Text Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either Text ByteString
BL64U.decodeBase64UnpaddedUntyped
    (ByteString -> Either Text ByteString)
-> (Text -> ByteString) -> Text -> Either Text ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
TL.encodeUtf8
{-# INLINE decodeBase64UnpaddedUntyped #-}

-- | Attempt to decode an unpadded, untyped lazy 'ByteString' value as Base64url, converting from
-- 'ByteString' to 'TL.Text' according to some encoding function. In practice,
-- This is something like 'decodeUtf8'', which may produce an error.
--
-- See: <https://tools.ietf.org/html/rfc4648#section-4 RFC-4648 section 4>
--
-- === __Examples__:
--
-- @
-- 'decodeBase64UnpaddedUntypedWith' 'TL.decodeUtf8''
--   :: 'ByteString' -> 'Either' ('Base64Error' 'UnicodeException') 'TL.Text'
-- @
--
decodeBase64UnpaddedUntypedWith
    :: (ByteString -> Either err TL.Text)
      -- ^ convert a bytestring to text (e.g. 'TL.decodeUtf8'')
    -> ByteString
      -- ^ Input text to decode
    -> Either (Base64Error err) TL.Text
decodeBase64UnpaddedUntypedWith :: forall err.
(ByteString -> Either err Text)
-> ByteString -> Either (Base64Error err) Text
decodeBase64UnpaddedUntypedWith ByteString -> Either err Text
f ByteString
t = case ByteString -> Either Text ByteString
BL64U.decodeBase64UnpaddedUntyped ByteString
t of
  Left Text
de -> Base64Error err -> Either (Base64Error err) Text
forall a b. a -> Either a b
Left (Base64Error err -> Either (Base64Error err) Text)
-> Base64Error err -> Either (Base64Error err) Text
forall a b. (a -> b) -> a -> b
$ Text -> Base64Error err
forall e. Text -> Base64Error e
DecodeError Text
de
  Right ByteString
a -> (err -> Base64Error err)
-> Either err Text -> Either (Base64Error err) Text
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first err -> Base64Error err
forall e. e -> Base64Error e
ConversionError (ByteString -> Either err Text
f ByteString
a)
{-# INLINE decodeBase64UnpaddedUntypedWith #-}

-- | Decode a padded Base64url encoded 'TL.Text' value
--
-- See: <https://tools.ietf.org/html/rfc4648#section-4 RFC-4648 section 4>
--
-- === __Examples__:
--
-- >>> decodeBase64Padded $ assertBase64 @'UrlPadded "PDw_Pj4="
-- "<<?>>"
--
decodeBase64Padded :: Base64 'UrlPadded TL.Text -> TL.Text
decodeBase64Padded :: Base64 'UrlPadded Text -> Text
decodeBase64Padded = ByteString -> Text
TL.decodeUtf8
  (ByteString -> Text)
-> (Base64 'UrlPadded Text -> ByteString)
-> Base64 'UrlPadded Text
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Base64 'UrlPadded ByteString -> ByteString
BL64U.decodeBase64Padded
  (Base64 'UrlPadded ByteString -> ByteString)
-> (Base64 'UrlPadded Text -> Base64 'UrlPadded ByteString)
-> Base64 'UrlPadded Text
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> ByteString)
-> Base64 'UrlPadded Text -> Base64 'UrlPadded ByteString
forall a b. (a -> b) -> Base64 'UrlPadded a -> Base64 'UrlPadded b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ByteString
TL.encodeUtf8
{-# INLINE decodeBase64Padded #-}

-- | Decode an untyped, padded Base64url encoded 'Text' value
--
-- See: <https://tools.ietf.org/html/rfc4648#section-4 RFC-4648 section 4>
--
-- === __Examples__:
--
-- >>> decodeBase64PaddedUntyped "PDw_Pj4="
-- Right "<<?>>"
--
decodeBase64PaddedUntyped :: TL.Text -> Either T.Text TL.Text
decodeBase64PaddedUntyped :: Text -> Either Text Text
decodeBase64PaddedUntyped = (ByteString -> Text) -> Either Text ByteString -> Either Text Text
forall a b. (a -> b) -> Either Text a -> Either Text b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Text
TL.decodeUtf8
  (Either Text ByteString -> Either Text Text)
-> (Text -> Either Text ByteString) -> Text -> Either Text Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either Text ByteString
BL64U.decodeBase64PaddedUntyped
  (ByteString -> Either Text ByteString)
-> (Text -> ByteString) -> Text -> Either Text ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
TL.encodeUtf8
{-# inline decodeBase64PaddedUntyped #-}

-- | Attempt to decode a padded, untyped lazy 'ByteString' value as Base64url, converting from
-- 'ByteString' to 'TL.Text' according to some encoding function. In practice,
-- This is something like 'decodeUtf8'', which may produce an error.
--
-- See: <https://tools.ietf.org/html/rfc4648#section-4 RFC-4648 section 4>
--
-- === __Example__:
--
-- @
-- 'decodeBase64PaddedWith' 'T.decodeUtf8''
--   :: 'ByteString' -> 'Either' ('Base64Error' 'UnicodeException') 'Text'
-- @
--
decodeBase64PaddedUntypedWith
    :: (ByteString -> Either err TL.Text)
      -- ^ convert a bytestring to text (e.g. 'TL.decodeUtf8'')
    -> ByteString
      -- ^ Input text to decode
    -> Either (Base64Error err) TL.Text
decodeBase64PaddedUntypedWith :: forall err.
(ByteString -> Either err Text)
-> ByteString -> Either (Base64Error err) Text
decodeBase64PaddedUntypedWith ByteString -> Either err Text
f ByteString
t = case ByteString -> Either Text ByteString
BL64U.decodeBase64PaddedUntyped ByteString
t of
  Left Text
de -> Base64Error err -> Either (Base64Error err) Text
forall a b. a -> Either a b
Left (Base64Error err -> Either (Base64Error err) Text)
-> Base64Error err -> Either (Base64Error err) Text
forall a b. (a -> b) -> a -> b
$ Text -> Base64Error err
forall e. Text -> Base64Error e
DecodeError Text
de
  Right ByteString
a -> (err -> Base64Error err)
-> Either err Text -> Either (Base64Error err) Text
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first err -> Base64Error err
forall e. e -> Base64Error e
ConversionError (ByteString -> Either err Text
f ByteString
a)
{-# INLINE decodeBase64PaddedUntypedWith #-}

-- | Leniently decode an untyped Base64url-encoded 'TL.Text'. This function
-- will not generate parse errors. If input data contains padding chars,
-- then the input will be parsed up until the first pad character.
--
-- __Note:__ This is not RFC 4648-compliant.
--
-- === __Examples__:
--
-- >>> decodeBase64Lenient "PDw_Pj4="
-- "<<?>>"
--
-- >>> decodeBase64Lenient "PDw_%%%$}Pj4"
-- "<<?>>"
--
decodeBase64Lenient :: TL.Text -> TL.Text
decodeBase64Lenient :: Text -> Text
decodeBase64Lenient = ByteString -> Text
TL.decodeUtf8
    (ByteString -> Text) -> (Text -> ByteString) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BL64U.decodeBase64Lenient
    (ByteString -> ByteString)
-> (Text -> ByteString) -> Text -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
TL.encodeUtf8
{-# INLINE decodeBase64Lenient #-}

-- | Tell whether an untyped 'TL.Text' value is Base64url-encoded
--
-- === __Examples__:
--
-- >>> isBase64Url "PDw_Pj4="
-- True
--
-- >>> isBase64Url "PDw_Pj4"
-- True
--
-- >>> isBase64Url "PDw_Pj"
-- False
--
isBase64Url :: TL.Text -> Bool
isBase64Url :: Text -> Bool
isBase64Url = ByteString -> Bool
BL64U.isBase64Url (ByteString -> Bool) -> (Text -> ByteString) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
TL.encodeUtf8
{-# INLINE isBase64Url #-}

-- | Tell whether an untyped 'TL.Text' value is a valid Base64url format.
--
-- This will not tell you whether or not this is a correct Base64url representation,
-- only that it conforms to the correct shape. To check whether it is a true
-- Base64 encoded 'TL.Text' value, use 'isBase64Url'.
--
-- === __Examples__:
--
-- >>> isValidBase64Url "PDw_Pj4="
-- True
--
-- >>> isValidBase64Url "PDw_Pj"
-- True
--
-- >>> isValidBase64Url "%"
-- False
--
isValidBase64Url :: TL.Text -> Bool
isValidBase64Url :: Text -> Bool
isValidBase64Url = ByteString -> Bool
BL64U.isValidBase64Url (ByteString -> Bool) -> (Text -> ByteString) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
TL.encodeUtf8
{-# INLINE isValidBase64Url #-}