module Amazonka.Data.Base64
( Base64 (..),
_Base64,
)
where
import qualified Amazonka.Bytes as Bytes
import Amazonka.Core.Lens.Internal (iso)
import Amazonka.Data.Body
import Amazonka.Data.ByteString
import Amazonka.Data.JSON
import Amazonka.Data.Query
import Amazonka.Data.Text
import Amazonka.Data.XML
import Amazonka.Prelude
import qualified Data.Text.Encoding as Text
newtype Base64 = Base64 {Base64 -> ByteString
unBase64 :: ByteString}
deriving stock (Base64 -> Base64 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Base64 -> Base64 -> Bool
$c/= :: Base64 -> Base64 -> Bool
== :: Base64 -> Base64 -> Bool
$c== :: Base64 -> Base64 -> Bool
Eq, ReadPrec [Base64]
ReadPrec Base64
Int -> ReadS Base64
ReadS [Base64]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Base64]
$creadListPrec :: ReadPrec [Base64]
readPrec :: ReadPrec Base64
$creadPrec :: ReadPrec Base64
readList :: ReadS [Base64]
$creadList :: ReadS [Base64]
readsPrec :: Int -> ReadS Base64
$creadsPrec :: Int -> ReadS Base64
Read, Eq Base64
Base64 -> Base64 -> Bool
Base64 -> Base64 -> Ordering
Base64 -> Base64 -> Base64
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Base64 -> Base64 -> Base64
$cmin :: Base64 -> Base64 -> Base64
max :: Base64 -> Base64 -> Base64
$cmax :: Base64 -> Base64 -> Base64
>= :: Base64 -> Base64 -> Bool
$c>= :: Base64 -> Base64 -> Bool
> :: Base64 -> Base64 -> Bool
$c> :: Base64 -> Base64 -> Bool
<= :: Base64 -> Base64 -> Bool
$c<= :: Base64 -> Base64 -> Bool
< :: Base64 -> Base64 -> Bool
$c< :: Base64 -> Base64 -> Bool
compare :: Base64 -> Base64 -> Ordering
$ccompare :: Base64 -> Base64 -> Ordering
Ord, forall x. Rep Base64 x -> Base64
forall x. Base64 -> Rep Base64 x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Base64 x -> Base64
$cfrom :: forall x. Base64 -> Rep Base64 x
Generic)
instance Hashable Base64
instance NFData Base64
_Base64 :: Iso' Base64 ByteString
_Base64 :: Iso' Base64 ByteString
_Base64 = forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Base64 -> ByteString
unBase64 ByteString -> Base64
Base64
instance FromText Base64 where
fromText :: Text -> Either String Base64
fromText = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Base64
Base64 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ByteArrayAccess a => a -> Either String ByteString
Bytes.decodeBase64 forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
Text.encodeUtf8
instance ToByteString Base64 where
toBS :: Base64 -> ByteString
toBS = forall a. ByteArrayAccess a => a -> ByteString
Bytes.encodeBase64 forall b c a. (b -> c) -> (a -> b) -> a -> c
. Base64 -> ByteString
unBase64
instance Show Base64 where
show :: Base64 -> String
show = forall a. Show a => a -> String
show forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToByteString a => a -> ByteString
toBS
instance ToText Base64 where
toText :: Base64 -> Text
toText = ByteString -> Text
Text.decodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToByteString a => a -> ByteString
toBS
instance ToQuery Base64 where
toQuery :: Base64 -> QueryString
toQuery = forall a. ToQuery a => a -> QueryString
toQuery forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToByteString a => a -> ByteString
toBS
instance FromXML Base64 where
parseXML :: [Node] -> Either String Base64
parseXML = forall a. FromText a => String -> [Node] -> Either String a
parseXMLText String
"Base64"
instance ToXML Base64 where
toXML :: Base64 -> XML
toXML = forall a. ToText a => a -> XML
toXMLText
instance FromJSON Base64 where
parseJSON :: Value -> Parser Base64
parseJSON = forall a. FromText a => String -> Value -> Parser a
parseJSONText String
"Base64"
instance ToJSON Base64 where
toJSON :: Base64 -> Value
toJSON = forall a. ToText a => a -> Value
toJSONText
instance ToHashedBody Base64 where
toHashed :: Base64 -> HashedBody
toHashed = forall a. ToHashedBody a => a -> HashedBody
toHashed forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToByteString a => a -> ByteString
toBS
instance ToBody Base64