{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE Trustworthy #-}
module Data.ByteString.Lazy.Base32
(
encodeBase32
, encodeBase32'
, encodeBase32Unpadded
, encodeBase32Unpadded'
, decodeBase32
, decodeBase32Unpadded
, decodeBase32Padded
, isBase32
, isValidBase32
) where
import Prelude hiding (all, elem)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Base32 as B32
import Data.ByteString.Base32.Internal.Utils (reChunkN)
import Data.ByteString.Lazy (elem, fromChunks, toChunks)
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
encodeBase32 :: ByteString -> TL.Text
encodeBase32 :: ByteString -> Text
encodeBase32 = ByteString -> Text
TL.decodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
encodeBase32'
{-# INLINE encodeBase32 #-}
encodeBase32' :: ByteString -> ByteString
encodeBase32' :: ByteString -> ByteString
encodeBase32' = [ByteString] -> ByteString
fromChunks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> ByteString
B32.encodeBase32'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [ByteString] -> [ByteString]
reChunkN Int
5
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [ByteString]
toChunks
decodeBase32 :: ByteString -> Either T.Text ByteString
decodeBase32 :: ByteString -> Either Text ByteString
decodeBase32 = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([ByteString] -> ByteString
fromChunks forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. a -> [a] -> [a]
:[]))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either Text ByteString
B32.decodeBase32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
BS.concat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [ByteString]
toChunks
{-# INLINE decodeBase32 #-}
encodeBase32Unpadded :: ByteString -> TL.Text
encodeBase32Unpadded :: ByteString -> Text
encodeBase32Unpadded = ByteString -> Text
TL.decodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
encodeBase32Unpadded'
{-# INLINE encodeBase32Unpadded #-}
encodeBase32Unpadded' :: ByteString -> ByteString
encodeBase32Unpadded' :: ByteString -> ByteString
encodeBase32Unpadded' = [ByteString] -> ByteString
fromChunks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> ByteString
B32.encodeBase32Unpadded'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [ByteString] -> [ByteString]
reChunkN Int
5
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [ByteString]
toChunks
decodeBase32Unpadded :: ByteString -> Either T.Text ByteString
decodeBase32Unpadded :: ByteString -> Either Text ByteString
decodeBase32Unpadded = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([ByteString] -> ByteString
fromChunks forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. a -> [a] -> [a]
:[]))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either Text ByteString
B32.decodeBase32Unpadded
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
BS.concat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [ByteString]
toChunks
{-# INLINE decodeBase32Unpadded #-}
decodeBase32Padded :: ByteString -> Either T.Text ByteString
decodeBase32Padded :: ByteString -> Either Text ByteString
decodeBase32Padded = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([ByteString] -> ByteString
fromChunks forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. a -> [a] -> [a]
:[]))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either Text ByteString
B32.decodeBase32Padded
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
BS.concat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [ByteString]
toChunks
{-# INLINE decodeBase32Padded #-}
isBase32 :: ByteString -> Bool
isBase32 :: ByteString -> Bool
isBase32 ByteString
bs = ByteString -> Bool
isValidBase32 ByteString
bs Bool -> Bool -> Bool
&& forall a b. Either a b -> Bool
isRight (ByteString -> Either Text ByteString
decodeBase32 ByteString
bs)
{-# INLINE isBase32 #-}
isValidBase32 :: ByteString -> Bool
isValidBase32 :: ByteString -> Bool
isValidBase32 = [ByteString] -> Bool
go forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [ByteString]
toChunks
where
go :: [ByteString] -> Bool
go [] = Bool
True
go [ByteString
c] = ByteString -> Bool
B32.isValidBase32 ByteString
c
go (ByteString
c:[ByteString]
cs) =
(Word8 -> Bool) -> ByteString -> Bool
BS.all (forall a b c. (a -> b -> c) -> b -> a -> c
flip Word8 -> ByteString -> Bool
elem ByteString
"ABCDEFGHIJKLMNOPQRSTUVWXYZ234567") ByteString
c
Bool -> Bool -> Bool
&& [ByteString] -> Bool
go [ByteString]
cs
{-# INLINE isValidBase32 #-}