module Amazonka.Data.ByteString
(
ByteString,
ByteStringLazy,
ToByteString (..),
showBS,
stripBS,
)
where
import Amazonka.Data.Text
import Amazonka.Prelude
import qualified Data.ByteString.Builder as Build
import qualified Data.ByteString.Char8 as BS8
import qualified Data.ByteString.Lazy as LBS
import qualified Data.CaseInsensitive as CI
import qualified Data.Char as Char
import qualified Data.Text.Encoding as Text
import qualified Network.HTTP.Types as HTTP
import qualified Numeric
showBS :: ToByteString a => a -> String
showBS :: forall a. ToByteString a => a -> String
showBS = ByteString -> String
BS8.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToByteString a => a -> ByteString
toBS
stripBS :: ByteString -> ByteString
stripBS :: ByteString -> ByteString
stripBS = (Char -> Bool) -> ByteString -> ByteString
BS8.dropWhile Char -> Bool
Char.isSpace forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> ByteString -> (ByteString, ByteString)
BS8.spanEnd Char -> Bool
Char.isSpace
class ToByteString a where
toBS :: a -> ByteString
default toBS :: ToText a => a -> ByteString
toBS = Text -> ByteString
Text.encodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToText a => a -> Text
toText
instance ToByteString ByteString where
toBS :: ByteString -> ByteString
toBS = forall a. a -> a
id
instance ToByteString ByteStringBuilder where
toBS :: ByteStringBuilder -> ByteString
toBS = forall a. ToByteString a => a -> ByteString
toBS forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteStringBuilder -> ByteString
Build.toLazyByteString
instance ToByteString ByteStringLazy where
toBS :: ByteString -> ByteString
toBS = ByteString -> ByteString
LBS.toStrict
instance ToByteString Text where
toBS :: Text -> ByteString
toBS = Text -> ByteString
Text.encodeUtf8
instance ToByteString String where
toBS :: String -> ByteString
toBS = String -> ByteString
BS8.pack
instance ToByteString Int where
toBS :: Int -> ByteString
toBS = forall a. ToByteString a => a -> ByteString
toBS forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ByteStringBuilder
Build.intDec
instance ToByteString Integer where
toBS :: Integer -> ByteString
toBS = forall a. ToByteString a => a -> ByteString
toBS forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> ByteStringBuilder
Build.integerDec
instance ToByteString Natural where
toBS :: Natural -> ByteString
toBS = forall a. ToByteString a => a -> ByteString
toBS forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Integral a => a -> Integer
toInteger
instance ToByteString Double where
toBS :: Double -> ByteString
toBS = forall a. ToByteString a => a -> ByteString
toBS 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 ToByteString HTTP.StdMethod where
toBS :: StdMethod -> ByteString
toBS = StdMethod -> ByteString
HTTP.renderStdMethod
instance ToByteString UTCTime where
toBS :: UTCTime -> ByteString
toBS = String -> ByteString
BS8.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
instance ToByteString a => ToByteString (CI a) where
toBS :: CI a -> ByteString
toBS = forall a. ToByteString a => a -> ByteString
toBS forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. CI s -> s
CI.original