{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DataKinds #-}
module Data.ByteString.Lazy.Base64
(
encodeBase64
, encodeBase64'
, decodeBase64
, decodeBase64Untyped
, decodeBase64Lenient
, isBase64
, isValidBase64
) where
import Data.Base64.Types
import qualified Data.ByteString as BS
import qualified Data.ByteString.Base64 as B64
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 'StdPadded TL.Text
encodeBase64 :: ByteString -> Base64 'StdPadded Text
encodeBase64 = (ByteString -> Text)
-> Base64 'StdPadded ByteString -> Base64 'StdPadded Text
forall a b. (a -> b) -> Base64 'StdPadded a -> Base64 'StdPadded b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Text
TL.decodeUtf8 (Base64 'StdPadded ByteString -> Base64 'StdPadded Text)
-> (ByteString -> Base64 'StdPadded ByteString)
-> ByteString
-> Base64 'StdPadded Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Base64 'StdPadded ByteString
encodeBase64'
{-# INLINE encodeBase64 #-}
encodeBase64' :: ByteString -> Base64 'StdPadded ByteString
encodeBase64' :: ByteString -> Base64 'StdPadded ByteString
encodeBase64' = ByteString -> Base64 'StdPadded ByteString
forall (k :: Alphabet) a. a -> Base64 k a
assertBase64
(ByteString -> Base64 'StdPadded ByteString)
-> (ByteString -> ByteString)
-> ByteString
-> Base64 'StdPadded 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 'StdPadded StrictByteString -> StrictByteString
forall (k :: Alphabet) a. Base64 k a -> a
extractBase64 (Base64 'StdPadded StrictByteString -> StrictByteString)
-> (StrictByteString -> Base64 'StdPadded StrictByteString)
-> StrictByteString
-> StrictByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictByteString -> Base64 'StdPadded StrictByteString
B64.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
{-# INLINE encodeBase64' #-}
decodeBase64 :: StdAlphabet k => Base64 k ByteString -> ByteString
decodeBase64 :: forall (k :: Alphabet).
StdAlphabet 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).
StdAlphabet k =>
Base64 k StrictByteString -> StrictByteString
B64.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
B64.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 #-}
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
B64.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 #-}
isBase64 :: ByteString -> Bool
isBase64 :: ByteString -> Bool
isBase64 ByteString
bs
= ByteString -> Bool
isValidBase64 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 isBase64 #-}
isValidBase64 :: ByteString -> Bool
isValidBase64 :: ByteString -> Bool
isValidBase64 = [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
B64.isValidBase64 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 isValidBase64 #-}