module Data.Text.Short.Encoding.Base16
( encodeBase16
, decodeBase16
, decodeBase16With
, decodeBase16Lenient
, isBase16
, isValidBase16
) where
import Data.Bifunctor (first)
import qualified Data.ByteString.Base16 as B16
import Data.ByteString.Short (ShortByteString)
import qualified Data.ByteString.Short.Base16 as BS16
import Data.Text (Text)
import qualified Data.Text.Encoding.Base16 as B16T
import Data.Text.Encoding.Base16.Error
import Data.Text.Short
import Data.Text.Short.Unsafe
encodeBase16 :: ShortText -> ShortText
encodeBase16 :: ShortText -> ShortText
encodeBase16 = ByteString -> ShortText
fromByteStringUnsafe (ByteString -> ShortText)
-> (ShortText -> ByteString) -> ShortText -> ShortText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
B16.encodeBase16' (ByteString -> ByteString)
-> (ShortText -> ByteString) -> ShortText -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> ByteString
toByteString
{-# INLINE encodeBase16 #-}
decodeBase16 :: ShortText -> Either Text ShortText
decodeBase16 :: ShortText -> Either Text ShortText
decodeBase16 = (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
B16T.decodeBase16 (Text -> Either Text Text)
-> (ShortText -> Text) -> ShortText -> Either Text Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> Text
toText
{-# INLINE decodeBase16 #-}
decodeBase16With
:: (ShortByteString -> Either err ShortText)
-> ShortText
-> Either (Base16Error err) ShortText
decodeBase16With :: (ShortByteString -> Either err ShortText)
-> ShortText -> Either (Base16Error err) ShortText
decodeBase16With ShortByteString -> Either err ShortText
f ShortText
t = case ShortByteString -> Either Text ShortByteString
BS16.decodeBase16 (ShortText -> ShortByteString
toShortByteString ShortText
t) of
Left Text
de -> Base16Error err -> Either (Base16Error err) ShortText
forall a b. a -> Either a b
Left (Base16Error err -> Either (Base16Error err) ShortText)
-> Base16Error err -> Either (Base16Error err) ShortText
forall a b. (a -> b) -> a -> b
$ Text -> Base16Error err
forall e. Text -> Base16Error e
DecodeError Text
de
Right ShortByteString
a -> (err -> Base16Error err)
-> Either err ShortText -> Either (Base16Error err) ShortText
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first err -> Base16Error err
forall e. e -> Base16Error e
ConversionError (ShortByteString -> Either err ShortText
f ShortByteString
a)
{-# INLINE decodeBase16With #-}
decodeBase16Lenient :: ShortText -> ShortText
decodeBase16Lenient :: ShortText -> ShortText
decodeBase16Lenient = Text -> ShortText
fromText (Text -> ShortText)
-> (ShortText -> Text) -> ShortText -> ShortText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
B16T.decodeBase16Lenient (Text -> Text) -> (ShortText -> Text) -> ShortText -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> Text
toText
{-# INLINE decodeBase16Lenient #-}
isBase16 :: ShortText -> Bool
isBase16 :: ShortText -> Bool
isBase16 = ByteString -> Bool
B16.isBase16 (ByteString -> Bool)
-> (ShortText -> ByteString) -> ShortText -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> ByteString
toByteString
{-# INLINE isBase16 #-}
isValidBase16 :: ShortText -> Bool
isValidBase16 :: ShortText -> Bool
isValidBase16 = ByteString -> Bool
B16.isValidBase16 (ByteString -> Bool)
-> (ShortText -> ByteString) -> ShortText -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> ByteString
toByteString
{-# INLINE isValidBase16 #-}