module Amazonka.Data.Text
( Text,
FromText (..),
ToText (..),
toTextCI,
showText,
)
where
import qualified Amazonka.Bytes as Bytes
import qualified Amazonka.Crypto as Crypto
import Amazonka.Prelude
import qualified Data.Attoparsec.Text as A
import qualified Data.ByteString.Char8 as BS8
import qualified Data.CaseInsensitive as CI
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import qualified Data.Text.Lazy as LText
import qualified Data.Text.Lazy.Builder as Build
import qualified Data.Text.Lazy.Builder.Int as Build
import qualified Data.Text.Lazy.Builder.Scientific as Build
import qualified Network.HTTP.Types as HTTP
import qualified Numeric
class FromText a where
fromText :: Text -> Either String a
instance FromText Text where
fromText :: Text -> Either String Text
fromText = forall (f :: * -> *) a. Applicative f => a -> f a
pure
instance FromText String where
fromText :: Text -> Either String String
fromText = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
Text.unpack
instance FromText ByteString where
fromText :: Text -> Either String ByteString
fromText = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
Text.encodeUtf8
instance (CI.FoldCase a, FromText a) => FromText (CI a) where
fromText :: Text -> Either String (CI a)
fromText = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall s. FoldCase s => s -> CI s
CI.mk forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromText a => Text -> Either String a
fromText
instance FromText Char where
fromText :: Text -> Either String Char
fromText = forall a. Parser a -> Text -> Either String a
A.parseOnly (Parser Text Char
A.anyChar forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall t. Chunk t => Parser t ()
A.endOfInput)
instance FromText Int where
fromText :: Text -> Either String Int
fromText = forall a. Parser a -> Text -> Either String a
A.parseOnly (forall a. Num a => Parser a -> Parser a
A.signed forall a. Integral a => Parser a
A.decimal forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall t. Chunk t => Parser t ()
A.endOfInput)
instance FromText Int64 where
fromText :: Text -> Either String Int64
fromText = forall a. Parser a -> Text -> Either String a
A.parseOnly (forall a. Num a => Parser a -> Parser a
A.signed forall a. Integral a => Parser a
A.decimal forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall t. Chunk t => Parser t ()
A.endOfInput)
instance FromText Integer where
fromText :: Text -> Either String Integer
fromText = forall a. Parser a -> Text -> Either String a
A.parseOnly (forall a. Num a => Parser a -> Parser a
A.signed forall a. Integral a => Parser a
A.decimal forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall t. Chunk t => Parser t ()
A.endOfInput)
instance FromText Scientific where
fromText :: Text -> Either String Scientific
fromText = forall a. Parser a -> Text -> Either String a
A.parseOnly (forall a. Num a => Parser a -> Parser a
A.signed Parser Text Scientific
A.scientific forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall t. Chunk t => Parser t ()
A.endOfInput)
instance FromText Natural where
fromText :: Text -> Either String Natural
fromText = forall a. Parser a -> Text -> Either String a
A.parseOnly (forall a. Integral a => Parser a
A.decimal forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall t. Chunk t => Parser t ()
A.endOfInput)
instance FromText Double where
fromText :: Text -> Either String Double
fromText = forall a. Parser a -> Text -> Either String a
A.parseOnly (forall a. Num a => Parser a -> Parser a
A.signed forall a. Fractional a => Parser a
A.rational forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall t. Chunk t => Parser t ()
A.endOfInput)
instance FromText Bool where
fromText :: Text -> Either String Bool
fromText Text
text =
case forall s. FoldCase s => s -> CI s
CI.mk Text
text of
CI Text
"true" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
True
CI Text
"false" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
CI Text
other -> forall a b. a -> Either a b
Left (String
"Failure parsing Bool from " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show CI Text
other forall a. [a] -> [a] -> [a]
++ String
".")
instance FromText HTTP.StdMethod where
fromText :: Text -> Either String StdMethod
fromText Text
text =
case ByteString -> Either ByteString StdMethod
HTTP.parseMethod (Text -> ByteString
Text.encodeUtf8 Text
text) of
Left ByteString
err -> forall a b. a -> Either a b
Left (ByteString -> String
BS8.unpack ByteString
err)
Right StdMethod
ok -> forall (f :: * -> *) a. Applicative f => a -> f a
pure StdMethod
ok
showText :: ToText a => a -> String
showText :: forall a. ToText a => a -> String
showText = Text -> String
Text.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToText a => a -> Text
toText
class ToText a where
toText :: a -> Text
instance ToText a => ToText (CI a) where
toText :: CI a -> Text
toText = forall a. ToText a => a -> Text
toText forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. CI s -> s
CI.original
instance ToText Text where
toText :: Text -> Text
toText = forall a. a -> a
id
instance ToText ByteString where
toText :: ByteString -> Text
toText = ByteString -> Text
Text.decodeUtf8
instance ToText Char where
toText :: Char -> Text
toText = Char -> Text
Text.singleton
instance ToText String where
toText :: String -> Text
toText = String -> Text
Text.pack
instance ToText Int where
toText :: Int -> Text
toText = TextBuilder -> Text
shortText forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Integral a => a -> TextBuilder
Build.decimal
instance ToText Int64 where
toText :: Int64 -> Text
toText = TextBuilder -> Text
shortText forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Integral a => a -> TextBuilder
Build.decimal
instance ToText Integer where
toText :: Integer -> Text
toText = TextBuilder -> Text
shortText forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Integral a => a -> TextBuilder
Build.decimal
instance ToText Natural where
toText :: Natural -> Text
toText = TextBuilder -> Text
shortText forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Integral a => a -> TextBuilder
Build.decimal
instance ToText Scientific where
toText :: Scientific -> Text
toText = TextBuilder -> Text
shortText forall b c a. (b -> c) -> (a -> b) -> a -> c
. Scientific -> TextBuilder
Build.scientificBuilder
instance ToText Double where
toText :: Double -> Text
toText = forall a. ToText a => a -> Text
toText forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a b. (a -> b) -> a -> b
$ String
"") forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. RealFloat a => Maybe Int -> a -> String -> String
Numeric.showFFloat forall a. Maybe a
Nothing
instance ToText HTTP.StdMethod where
toText :: StdMethod -> Text
toText = forall a. ToText a => a -> Text
toText forall b c a. (b -> c) -> (a -> b) -> a -> c
. StdMethod -> ByteString
HTTP.renderStdMethod
instance ToText (Crypto.Digest a) where
toText :: Digest a -> Text
toText = forall a. ToText a => a -> Text
toText forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ByteArrayAccess a => a -> ByteString
Bytes.encodeBase16
instance ToText Bool where
toText :: Bool -> Text
toText Bool
True = Text
"true"
toText Bool
False = Text
"false"
shortText :: TextBuilder -> Text
shortText :: TextBuilder -> Text
shortText = Text -> Text
LText.toStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> TextBuilder -> Text
Build.toLazyTextWith Int
32
toTextCI :: ToText a => a -> CI Text
toTextCI :: forall a. ToText a => a -> CI Text
toTextCI = forall s. FoldCase s => s -> CI s
CI.mk forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToText a => a -> Text
toText