{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
module Data.ByteString.Lazy.Base64.URL
(
encodeBase64
, encodeBase64'
, encodeBase64Unpadded
, encodeBase64Unpadded'
, decodeBase64
, decodeBase64Untyped
, decodeBase64Unpadded
, decodeBase64UnpaddedUntyped
, decodeBase64Padded
, decodeBase64PaddedUntyped
, decodeBase64Lenient
, isBase64Url
, isValidBase64Url
) where
import Data.Base64.Types
import qualified Data.ByteString as BS
import qualified Data.ByteString.Base64.URL as B64U
import Data.ByteString.Base64.Internal.Utils (reChunkN)
import Data.ByteString.Lazy (fromChunks, toChunks)
import qualified Data.ByteString.Lazy as BL
import Data.ByteString.Lazy.Internal (ByteString(..))
import Data.Either (isRight)
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL
encodeBase64 :: ByteString -> Base64 'UrlPadded TL.Text
encodeBase64 :: ByteString -> Base64 'UrlPadded Text
encodeBase64 = (ByteString -> Text)
-> Base64 'UrlPadded ByteString -> Base64 'UrlPadded Text
forall a b. (a -> b) -> Base64 'UrlPadded a -> Base64 'UrlPadded b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Text
TL.decodeUtf8 (Base64 'UrlPadded ByteString -> Base64 'UrlPadded Text)
-> (ByteString -> Base64 'UrlPadded ByteString)
-> ByteString
-> Base64 'UrlPadded Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Base64 'UrlPadded ByteString
encodeBase64'
{-# INLINE encodeBase64 #-}
encodeBase64' :: ByteString -> Base64 'UrlPadded ByteString
encodeBase64' :: ByteString -> Base64 'UrlPadded ByteString
encodeBase64' = ByteString -> Base64 'UrlPadded ByteString
forall (k :: Alphabet) a. a -> Base64 k a
assertBase64 (ByteString -> Base64 'UrlPadded ByteString)
-> (ByteString -> ByteString)
-> ByteString
-> Base64 'UrlPadded ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [StrictByteString] -> ByteString
fromChunks
([StrictByteString] -> ByteString)
-> (ByteString -> [StrictByteString]) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (StrictByteString -> StrictByteString)
-> [StrictByteString] -> [StrictByteString]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Base64 'UrlPadded StrictByteString -> StrictByteString
forall (k :: Alphabet) a. Base64 k a -> a
extractBase64 (Base64 'UrlPadded StrictByteString -> StrictByteString)
-> (StrictByteString -> Base64 'UrlPadded StrictByteString)
-> StrictByteString
-> StrictByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictByteString -> Base64 'UrlPadded StrictByteString
B64U.encodeBase64')
([StrictByteString] -> [StrictByteString])
-> (ByteString -> [StrictByteString])
-> ByteString
-> [StrictByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [StrictByteString] -> [StrictByteString]
reChunkN Int
3
([StrictByteString] -> [StrictByteString])
-> (ByteString -> [StrictByteString])
-> ByteString
-> [StrictByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [StrictByteString]
toChunks
decodeBase64
:: UrlAlphabet k
=> Base64 k ByteString
-> ByteString
decodeBase64 :: forall (k :: Alphabet).
UrlAlphabet k =>
Base64 k ByteString -> ByteString
decodeBase64 = [StrictByteString] -> ByteString
fromChunks
([StrictByteString] -> ByteString)
-> (Base64 k ByteString -> [StrictByteString])
-> Base64 k ByteString
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictByteString -> [StrictByteString]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(StrictByteString -> [StrictByteString])
-> (Base64 k ByteString -> StrictByteString)
-> Base64 k ByteString
-> [StrictByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Base64 k StrictByteString -> StrictByteString
forall (k :: Alphabet).
UrlAlphabet k =>
Base64 k StrictByteString -> StrictByteString
B64U.decodeBase64
(Base64 k StrictByteString -> StrictByteString)
-> (Base64 k ByteString -> Base64 k StrictByteString)
-> Base64 k ByteString
-> StrictByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> StrictByteString)
-> Base64 k ByteString -> Base64 k StrictByteString
forall a b. (a -> b) -> Base64 k a -> Base64 k b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([StrictByteString] -> StrictByteString
BS.concat ([StrictByteString] -> StrictByteString)
-> (ByteString -> [StrictByteString])
-> ByteString
-> StrictByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [StrictByteString]
toChunks)
{-# INLINE decodeBase64 #-}
decodeBase64Untyped :: ByteString -> Either T.Text ByteString
decodeBase64Untyped :: ByteString -> Either Text ByteString
decodeBase64Untyped = (StrictByteString -> ByteString)
-> Either Text StrictByteString -> Either Text ByteString
forall a b. (a -> b) -> Either Text a -> Either Text b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([StrictByteString] -> ByteString
fromChunks ([StrictByteString] -> ByteString)
-> (StrictByteString -> [StrictByteString])
-> StrictByteString
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictByteString -> [StrictByteString]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure)
(Either Text StrictByteString -> Either Text ByteString)
-> (ByteString -> Either Text StrictByteString)
-> ByteString
-> Either Text ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictByteString -> Either Text StrictByteString
B64U.decodeBase64Untyped
(StrictByteString -> Either Text StrictByteString)
-> (ByteString -> StrictByteString)
-> ByteString
-> Either Text StrictByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [StrictByteString] -> StrictByteString
BS.concat
([StrictByteString] -> StrictByteString)
-> (ByteString -> [StrictByteString])
-> ByteString
-> StrictByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [StrictByteString]
toChunks
{-# INLINE decodeBase64Untyped #-}
encodeBase64Unpadded :: ByteString -> Base64 'UrlUnpadded TL.Text
encodeBase64Unpadded :: ByteString -> Base64 'UrlUnpadded Text
encodeBase64Unpadded = (ByteString -> Text)
-> Base64 'UrlUnpadded ByteString -> Base64 'UrlUnpadded Text
forall a b.
(a -> b) -> Base64 'UrlUnpadded a -> Base64 'UrlUnpadded b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Text
TL.decodeUtf8 (Base64 'UrlUnpadded ByteString -> Base64 'UrlUnpadded Text)
-> (ByteString -> Base64 'UrlUnpadded ByteString)
-> ByteString
-> Base64 'UrlUnpadded Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Base64 'UrlUnpadded ByteString
encodeBase64Unpadded'
{-# INLINE encodeBase64Unpadded #-}
encodeBase64Unpadded' :: ByteString -> Base64 'UrlUnpadded ByteString
encodeBase64Unpadded' :: ByteString -> Base64 'UrlUnpadded ByteString
encodeBase64Unpadded' = ByteString -> Base64 'UrlUnpadded ByteString
forall (k :: Alphabet) a. a -> Base64 k a
assertBase64
(ByteString -> Base64 'UrlUnpadded ByteString)
-> (ByteString -> ByteString)
-> ByteString
-> Base64 'UrlUnpadded ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [StrictByteString] -> ByteString
fromChunks
([StrictByteString] -> ByteString)
-> (ByteString -> [StrictByteString]) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (StrictByteString -> StrictByteString)
-> [StrictByteString] -> [StrictByteString]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Base64 'UrlUnpadded StrictByteString -> StrictByteString
forall (k :: Alphabet) a. Base64 k a -> a
extractBase64 (Base64 'UrlUnpadded StrictByteString -> StrictByteString)
-> (StrictByteString -> Base64 'UrlUnpadded StrictByteString)
-> StrictByteString
-> StrictByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictByteString -> Base64 'UrlUnpadded StrictByteString
B64U.encodeBase64Unpadded')
([StrictByteString] -> [StrictByteString])
-> (ByteString -> [StrictByteString])
-> ByteString
-> [StrictByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [StrictByteString] -> [StrictByteString]
reChunkN Int
3
([StrictByteString] -> [StrictByteString])
-> (ByteString -> [StrictByteString])
-> ByteString
-> [StrictByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [StrictByteString]
toChunks
decodeBase64Unpadded :: Base64 'UrlUnpadded ByteString -> ByteString
decodeBase64Unpadded :: Base64 'UrlUnpadded ByteString -> ByteString
decodeBase64Unpadded = [StrictByteString] -> ByteString
fromChunks
([StrictByteString] -> ByteString)
-> (Base64 'UrlUnpadded ByteString -> [StrictByteString])
-> Base64 'UrlUnpadded ByteString
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictByteString -> [StrictByteString]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(StrictByteString -> [StrictByteString])
-> (Base64 'UrlUnpadded ByteString -> StrictByteString)
-> Base64 'UrlUnpadded ByteString
-> [StrictByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Base64 'UrlUnpadded StrictByteString -> StrictByteString
B64U.decodeBase64Unpadded
(Base64 'UrlUnpadded StrictByteString -> StrictByteString)
-> (Base64 'UrlUnpadded ByteString
-> Base64 'UrlUnpadded StrictByteString)
-> Base64 'UrlUnpadded ByteString
-> StrictByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> StrictByteString)
-> Base64 'UrlUnpadded ByteString
-> Base64 'UrlUnpadded StrictByteString
forall a b.
(a -> b) -> Base64 'UrlUnpadded a -> Base64 'UrlUnpadded b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([StrictByteString] -> StrictByteString
BS.concat ([StrictByteString] -> StrictByteString)
-> (ByteString -> [StrictByteString])
-> ByteString
-> StrictByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [StrictByteString]
toChunks)
decodeBase64UnpaddedUntyped :: ByteString -> Either T.Text ByteString
decodeBase64UnpaddedUntyped :: ByteString -> Either Text ByteString
decodeBase64UnpaddedUntyped = (StrictByteString -> ByteString)
-> Either Text StrictByteString -> Either Text ByteString
forall a b. (a -> b) -> Either Text a -> Either Text b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([StrictByteString] -> ByteString
fromChunks ([StrictByteString] -> ByteString)
-> (StrictByteString -> [StrictByteString])
-> StrictByteString
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (StrictByteString -> [StrictByteString] -> [StrictByteString]
forall a. a -> [a] -> [a]
:[]))
(Either Text StrictByteString -> Either Text ByteString)
-> (ByteString -> Either Text StrictByteString)
-> ByteString
-> Either Text ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictByteString -> Either Text StrictByteString
B64U.decodeBase64UnpaddedUntyped
(StrictByteString -> Either Text StrictByteString)
-> (ByteString -> StrictByteString)
-> ByteString
-> Either Text StrictByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [StrictByteString] -> StrictByteString
BS.concat
([StrictByteString] -> StrictByteString)
-> (ByteString -> [StrictByteString])
-> ByteString
-> StrictByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [StrictByteString]
toChunks
{-# INLINE decodeBase64UnpaddedUntyped #-}
decodeBase64Padded :: Base64 'UrlPadded ByteString -> ByteString
decodeBase64Padded :: Base64 'UrlPadded ByteString -> ByteString
decodeBase64Padded = [StrictByteString] -> ByteString
fromChunks
([StrictByteString] -> ByteString)
-> (Base64 'UrlPadded ByteString -> [StrictByteString])
-> Base64 'UrlPadded ByteString
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictByteString -> [StrictByteString]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(StrictByteString -> [StrictByteString])
-> (Base64 'UrlPadded ByteString -> StrictByteString)
-> Base64 'UrlPadded ByteString
-> [StrictByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Base64 'UrlPadded StrictByteString -> StrictByteString
B64U.decodeBase64Padded
(Base64 'UrlPadded StrictByteString -> StrictByteString)
-> (Base64 'UrlPadded ByteString
-> Base64 'UrlPadded StrictByteString)
-> Base64 'UrlPadded ByteString
-> StrictByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> StrictByteString)
-> Base64 'UrlPadded ByteString
-> Base64 'UrlPadded StrictByteString
forall a b. (a -> b) -> Base64 'UrlPadded a -> Base64 'UrlPadded b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([StrictByteString] -> StrictByteString
BS.concat ([StrictByteString] -> StrictByteString)
-> (ByteString -> [StrictByteString])
-> ByteString
-> StrictByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [StrictByteString]
toChunks)
{-# inline decodeBase64Padded #-}
decodeBase64PaddedUntyped :: ByteString -> Either T.Text ByteString
decodeBase64PaddedUntyped :: ByteString -> Either Text ByteString
decodeBase64PaddedUntyped = (StrictByteString -> ByteString)
-> Either Text StrictByteString -> Either Text ByteString
forall a b. (a -> b) -> Either Text a -> Either Text b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([StrictByteString] -> ByteString
fromChunks ([StrictByteString] -> ByteString)
-> (StrictByteString -> [StrictByteString])
-> StrictByteString
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (StrictByteString -> [StrictByteString] -> [StrictByteString]
forall a. a -> [a] -> [a]
:[]))
(Either Text StrictByteString -> Either Text ByteString)
-> (ByteString -> Either Text StrictByteString)
-> ByteString
-> Either Text ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictByteString -> Either Text StrictByteString
B64U.decodeBase64PaddedUntyped
(StrictByteString -> Either Text StrictByteString)
-> (ByteString -> StrictByteString)
-> ByteString
-> Either Text StrictByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [StrictByteString] -> StrictByteString
BS.concat
([StrictByteString] -> StrictByteString)
-> (ByteString -> [StrictByteString])
-> ByteString
-> StrictByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [StrictByteString]
toChunks
{-# INLINE decodeBase64PaddedUntyped #-}
decodeBase64Lenient :: ByteString -> ByteString
decodeBase64Lenient :: ByteString -> ByteString
decodeBase64Lenient = [StrictByteString] -> ByteString
fromChunks
([StrictByteString] -> ByteString)
-> (ByteString -> [StrictByteString]) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (StrictByteString -> StrictByteString)
-> [StrictByteString] -> [StrictByteString]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap StrictByteString -> StrictByteString
B64U.decodeBase64Lenient
([StrictByteString] -> [StrictByteString])
-> (ByteString -> [StrictByteString])
-> ByteString
-> [StrictByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [StrictByteString] -> [StrictByteString]
reChunkN Int
4
([StrictByteString] -> [StrictByteString])
-> (ByteString -> [StrictByteString])
-> ByteString
-> [StrictByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (StrictByteString -> StrictByteString)
-> [StrictByteString] -> [StrictByteString]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Word8 -> Bool) -> StrictByteString -> StrictByteString
BS.filter (Word8 -> ByteString -> Bool
`BL.elem` ByteString
"ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789-_="))
([StrictByteString] -> [StrictByteString])
-> (ByteString -> [StrictByteString])
-> ByteString
-> [StrictByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [StrictByteString]
toChunks
{-# INLINE decodeBase64Lenient #-}
isBase64Url :: ByteString -> Bool
isBase64Url :: ByteString -> Bool
isBase64Url ByteString
bs
= ByteString -> Bool
isValidBase64Url ByteString
bs
Bool -> Bool -> Bool
&& Either Text ByteString -> Bool
forall a b. Either a b -> Bool
isRight (ByteString -> Either Text ByteString
decodeBase64Untyped ByteString
bs)
{-# INLINE isBase64Url #-}
isValidBase64Url :: ByteString -> Bool
isValidBase64Url :: ByteString -> Bool
isValidBase64Url = [StrictByteString] -> Bool
go ([StrictByteString] -> Bool)
-> (ByteString -> [StrictByteString]) -> ByteString -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [StrictByteString]
toChunks
where
go :: [StrictByteString] -> Bool
go [] = Bool
True
go [StrictByteString
c] = StrictByteString -> Bool
B64U.isValidBase64Url StrictByteString
c
go (StrictByteString
c:[StrictByteString]
cs) =
(Word8 -> Bool) -> StrictByteString -> Bool
BS.all (Word8 -> ByteString -> Bool
`BL.elem` ByteString
"ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789-_") StrictByteString
c
Bool -> Bool -> Bool
&& [StrictByteString] -> Bool
go [StrictByteString]
cs
{-# INLINE isValidBase64Url #-}