{-# LANGUAGE Trustworthy #-}
module Data.Text.Short.Encoding.Base64.URL
(
encodeBase64
, encodeBase64Unpadded
, decodeBase64
, decodeBase64With
, decodeBase64Unpadded
, decodeBase64UnpaddedWith
, decodeBase64Padded
, decodeBase64PaddedWith
, decodeBase64Lenient
, isBase64Url
, isValidBase64Url
) where
import Data.Bifunctor (first)
import qualified Data.ByteString.Base64.URL as B64U
import Data.ByteString.Short (ShortByteString)
import qualified Data.ByteString.Short.Base64.URL as BS64U
import Data.Text (Text)
import qualified Data.Text.Encoding.Base64.URL as B64TU
import Data.Text.Encoding.Base64.Error
import Data.Text.Short
import Data.Text.Short.Unsafe
encodeBase64 :: ShortText -> ShortText
encodeBase64 :: ShortText -> ShortText
encodeBase64 = ByteString -> ShortText
fromByteStringUnsafe
(ByteString -> ShortText)
-> (ShortText -> ByteString) -> ShortText -> ShortText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
B64U.encodeBase64'
(ByteString -> ByteString)
-> (ShortText -> ByteString) -> ShortText -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> ByteString
toByteString
{-# INLINE encodeBase64 #-}
decodeBase64 :: ShortText -> Either Text ShortText
decodeBase64 :: ShortText -> Either Text ShortText
decodeBase64 = (Text -> ShortText) -> Either Text Text -> Either Text ShortText
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ShortText
fromText (Either Text Text -> Either Text ShortText)
-> (ShortText -> Either Text Text)
-> ShortText
-> Either Text ShortText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either Text Text
B64TU.decodeBase64 (Text -> Either Text Text)
-> (ShortText -> Text) -> ShortText -> Either Text Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> Text
toText
{-# INLINE decodeBase64 #-}
decodeBase64With
:: (ShortByteString -> Either err ShortText)
-> ShortByteString
-> Either (Base64Error err) ShortText
decodeBase64With :: (ShortByteString -> Either err ShortText)
-> ShortByteString -> Either (Base64Error err) ShortText
decodeBase64With ShortByteString -> Either err ShortText
f ShortByteString
t = case ShortByteString -> Either Text ShortByteString
BS64U.decodeBase64 ShortByteString
t of
Left Text
de -> Base64Error err -> Either (Base64Error err) ShortText
forall a b. a -> Either a b
Left (Base64Error err -> Either (Base64Error err) ShortText)
-> Base64Error err -> Either (Base64Error err) ShortText
forall a b. (a -> b) -> a -> b
$ Text -> Base64Error err
forall e. Text -> Base64Error e
DecodeError Text
de
Right ShortByteString
a -> (err -> Base64Error err)
-> Either err ShortText -> Either (Base64Error err) ShortText
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 (ShortByteString -> Either err ShortText
f ShortByteString
a)
{-# INLINE decodeBase64With #-}
encodeBase64Unpadded :: ShortText -> ShortText
encodeBase64Unpadded :: ShortText -> ShortText
encodeBase64Unpadded = ByteString -> ShortText
fromByteStringUnsafe
(ByteString -> ShortText)
-> (ShortText -> ByteString) -> ShortText -> ShortText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
B64U.encodeBase64Unpadded'
(ByteString -> ByteString)
-> (ShortText -> ByteString) -> ShortText -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> ByteString
toByteString
{-# INLINE encodeBase64Unpadded #-}
decodeBase64Unpadded :: ShortText -> Either Text ShortText
decodeBase64Unpadded :: ShortText -> Either Text ShortText
decodeBase64Unpadded = (Text -> ShortText) -> Either Text Text -> Either Text ShortText
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ShortText
fromText (Either Text Text -> Either Text ShortText)
-> (ShortText -> Either Text Text)
-> ShortText
-> Either Text ShortText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either Text Text
B64TU.decodeBase64Unpadded (Text -> Either Text Text)
-> (ShortText -> Text) -> ShortText -> Either Text Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> Text
toText
{-# INLINE decodeBase64Unpadded #-}
decodeBase64UnpaddedWith
:: (ShortByteString -> Either err ShortText)
-> ShortByteString
-> Either (Base64Error err) ShortText
decodeBase64UnpaddedWith :: (ShortByteString -> Either err ShortText)
-> ShortByteString -> Either (Base64Error err) ShortText
decodeBase64UnpaddedWith ShortByteString -> Either err ShortText
f ShortByteString
t = case ShortByteString -> Either Text ShortByteString
BS64U.decodeBase64Unpadded ShortByteString
t of
Left Text
de -> Base64Error err -> Either (Base64Error err) ShortText
forall a b. a -> Either a b
Left (Base64Error err -> Either (Base64Error err) ShortText)
-> Base64Error err -> Either (Base64Error err) ShortText
forall a b. (a -> b) -> a -> b
$ Text -> Base64Error err
forall e. Text -> Base64Error e
DecodeError Text
de
Right ShortByteString
a -> (err -> Base64Error err)
-> Either err ShortText -> Either (Base64Error err) ShortText
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 (ShortByteString -> Either err ShortText
f ShortByteString
a)
{-# INLINE decodeBase64UnpaddedWith #-}
decodeBase64Padded :: ShortText -> Either Text ShortText
decodeBase64Padded :: ShortText -> Either Text ShortText
decodeBase64Padded = (Text -> ShortText) -> Either Text Text -> Either Text ShortText
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ShortText
fromText (Either Text Text -> Either Text ShortText)
-> (ShortText -> Either Text Text)
-> ShortText
-> Either Text ShortText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either Text Text
B64TU.decodeBase64Padded (Text -> Either Text Text)
-> (ShortText -> Text) -> ShortText -> Either Text Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> Text
toText
{-# INLINE decodeBase64Padded #-}
decodeBase64PaddedWith
:: (ShortByteString -> Either err ShortText)
-> ShortByteString
-> Either (Base64Error err) ShortText
decodeBase64PaddedWith :: (ShortByteString -> Either err ShortText)
-> ShortByteString -> Either (Base64Error err) ShortText
decodeBase64PaddedWith ShortByteString -> Either err ShortText
f ShortByteString
t = case ShortByteString -> Either Text ShortByteString
BS64U.decodeBase64Padded ShortByteString
t of
Left Text
de -> Base64Error err -> Either (Base64Error err) ShortText
forall a b. a -> Either a b
Left (Base64Error err -> Either (Base64Error err) ShortText)
-> Base64Error err -> Either (Base64Error err) ShortText
forall a b. (a -> b) -> a -> b
$ Text -> Base64Error err
forall e. Text -> Base64Error e
DecodeError Text
de
Right ShortByteString
a -> (err -> Base64Error err)
-> Either err ShortText -> Either (Base64Error err) ShortText
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 (ShortByteString -> Either err ShortText
f ShortByteString
a)
{-# INLINE decodeBase64PaddedWith #-}
decodeBase64Lenient :: ShortText -> ShortText
decodeBase64Lenient :: ShortText -> ShortText
decodeBase64Lenient = Text -> ShortText
fromText (Text -> ShortText)
-> (ShortText -> Text) -> ShortText -> ShortText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
B64TU.decodeBase64Lenient (Text -> Text) -> (ShortText -> Text) -> ShortText -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> Text
toText
{-# INLINE decodeBase64Lenient #-}
isBase64Url :: ShortText -> Bool
isBase64Url :: ShortText -> Bool
isBase64Url = ByteString -> Bool
B64U.isBase64Url (ByteString -> Bool)
-> (ShortText -> ByteString) -> ShortText -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> ByteString
toByteString
{-# INLINE isBase64Url #-}
isValidBase64Url :: ShortText -> Bool
isValidBase64Url :: ShortText -> Bool
isValidBase64Url = ByteString -> Bool
B64U.isValidBase64Url (ByteString -> Bool)
-> (ShortText -> ByteString) -> ShortText -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> ByteString
toByteString
{-# INLINE isValidBase64Url #-}