Safe Haskell | None |
---|---|
Language | Haskell2010 |
Network.AWS.Data
Contents
Description
Serialisation classes and primitives for the various formats used to communicate with AWS.
- type LazyByteString = ByteString
- class ToByteString a where
- toBS :: a -> ByteString
- showBS :: ToByteString a => a -> String
- class ToBuilder a where
- buildBS :: ToBuilder a => a -> ByteString
- stripBS :: ByteString -> ByteString
- data Base64
- class FromText a where
- fromText :: FromText a => Text -> Either String a
- takeText :: Parser Text
- matchCI :: Text -> a -> Parser a
- class ToText a where
- showText :: ToText a => a -> String
- newtype Nat = Nat {}
- _Nat :: Iso' Nat Natural
- data Format
- data Time :: Format -> * where
- Time :: UTCTime -> Time a
- LocaleTime :: TimeLocale -> UTCTime -> Time a
- _Time :: Iso' (Time a) UTCTime
- data UTCTime :: *
- type RFC822 = Time RFC822Format
- type ISO8601 = Time ISO8601Format
- type BasicTime = Time BasicFormat
- type AWSTime = Time AWSFormat
- type POSIX = Time POSIXFormat
- newtype Sensitive a = Sensitive {
- desensitise :: a
- _Sensitive :: Iso' (Sensitive a) a
- data RsBody = RsBody (ResumableSource (ResourceT IO) ByteString)
- _RsBody :: Iso' RsBody (ResumableSource (ResourceT IO) ByteString)
- connectBody :: MonadResource m => RsBody -> Sink ByteString m a -> m a
- data RqBody = RqBody {}
- bdyHash :: Lens' RqBody (Digest SHA256)
- bdyBody :: Lens' RqBody RequestBody
- bodyHash :: RqBody -> ByteString
- class ToBody a where
- sourceBody :: Digest SHA256 -> Int64 -> Source IO ByteString -> RqBody
- sourceHandle :: Digest SHA256 -> Int64 -> Handle -> RqBody
- sourceFile :: Digest SHA256 -> Int64 -> FilePath -> RqBody
- sourceFileIO :: MonadIO m => FilePath -> m RqBody
- sourcePopper :: Source IO ByteString -> GivesPopper ()
- (~:) :: FromText a => ResponseHeaders -> HeaderName -> Either String a
- (~:?) :: FromText a => ResponseHeaders -> HeaderName -> Either String (Maybe a)
- class ToHeaders a where
- (=:) :: ToHeader a => HeaderName -> a -> [Header]
- hdr :: HeaderName -> ByteString -> [Header] -> [Header]
- hdrs :: [Header] -> [Header] -> [Header]
- toHeaderText :: ToText a => HeaderName -> a -> [Header]
- class ToHeader a where
- toHeader :: HeaderName -> a -> [Header]
- hHost :: HeaderName
- hAMZToken :: HeaderName
- hAMZTarget :: HeaderName
- hAMZAlgorithm :: HeaderName
- hAMZCredential :: HeaderName
- hAMZExpires :: HeaderName
- hAMZSignedHeaders :: HeaderName
- hAMZContentSHA256 :: HeaderName
- hAMZAuth :: HeaderName
- hAMZDate :: HeaderName
- hMetaPrefix :: HeaderName
- class ToPath a where
- class ToQuery a where
- renderQuery :: Query -> ByteString
- data Query
- valuesOf :: Traversal' Query (Maybe ByteString)
- pair :: ToQuery a => ByteString -> a -> Query -> Query
- (=?) :: ToQuery a => ByteString -> a -> Query
- collapseURI :: ByteString -> ByteString
- class FromXML a where
- decodeXML :: LazyByteString -> Either String [Node]
- parseXMLText :: FromText a => String -> [Node] -> Either String a
- childNodes :: Text -> Node -> Maybe [Node]
- findElement :: Text -> [Node] -> Either String [Node]
- withContent :: String -> (Text -> Either String a) -> [Node] -> Either String a
- withElement :: Text -> ([Node] -> Either String a) -> [Node] -> Either String a
- withNode :: String -> (Node -> Either String a) -> [Node] -> Either String a
- localName :: Node -> Maybe Text
- (.@) :: FromXML a => [Node] -> Text -> Either String a
- (.@?) :: FromXML a => [Node] -> Text -> Either String (Maybe a)
- class ToXML a where
- class ToXMLRoot a where
- encodeXML :: ToXMLRoot a => a -> LazyByteString
- toXMLText :: ToText a => a -> [Node]
- namespaced :: Text -> Text -> [Node] -> Element
- element :: Name -> [Node] -> Element
- nodes :: Name -> [Node] -> [Node]
- (=@) :: ToXML a => Name -> a -> Node
- unsafeToXML :: (Show a, ToXML a) => a -> Node
- class FromJSON a where
- parseJSONText :: FromText a => String -> Value -> Parser a
- withObject :: String -> (Object -> Parser a) -> Value -> Parser a
- (.:) :: FromJSON a => Object -> Text -> Parser a
- (.:?) :: FromJSON a => Object -> Text -> Parser (Maybe a)
- (.:>) :: FromJSON a => Object -> Text -> Either String a
- (.:?>) :: FromJSON a => Object -> Text -> Either String (Maybe a)
- class ToJSON a where
- toJSONText :: ToText a => a -> Value
- object :: [Pair] -> Value
- (.=) :: ToJSON a => Text -> a -> Pair
- newtype List e a = List {
- list :: [a]
- newtype List1 e a = List1 {}
- _List :: (Coercible a b, Coercible b a) => Iso' (List e a) [b]
- _List1 :: (Coercible a b, Coercible b a) => Iso' (List1 e a) (NonEmpty b)
- fromList1 :: List1 e a -> List e a
- toList1 :: List e a -> Either String (List1 e a)
- newtype Map k v = Map {}
- _Map :: (Coercible a b, Coercible b a) => Iso' (Map k a) (HashMap k b)
- (~::) :: ResponseHeaders -> CI Text -> Either String (Map (CI Text) Text)
- newtype EMap e i j k v = EMap {}
- _EMap :: (Coercible a b, Coercible b a) => Iso' (EMap e i j k a) (HashMap k b)
ByteString
type LazyByteString = ByteString Source
class ToByteString a where Source
Minimal complete definition
Nothing
Methods
toBS :: a -> ByteString Source
Instances
showBS :: ToByteString a => a -> String Source
buildBS :: ToBuilder a => a -> ByteString Source
stripBS :: ByteString -> ByteString Source
Base64 encoded binary data.
Text
Instances
Instances
ToText Bool | |
ToText Double | |
ToText Int | |
ToText Int64 | |
ToText Integer | |
ToText ByteString | |
ToText Text | |
ToText StdMethod | |
ToText Natural | |
ToText RsBody | |
ToText RqBody | |
ToText Query | |
ToText Base64 | |
ToText Nat | |
ToText POSIX | |
ToText AWSTime | |
ToText BasicTime | |
ToText ISO8601 | |
ToText RFC822 | |
ToText Action | |
ToText Zone | |
ToText Region | |
ToText SecretKey | |
ToText AccessKey | |
ToText Credentials | |
ToText a => ToText [a] | |
ToText a => ToText (CI a) | |
ToText (Digest a) | |
ToText (Response a) | |
ToText a => ToText (Sensitive a) | |
ToText (Request a) | |
(ToText a, ToText b) => ToText (a, b) | |
ToText (Signed a v) |
Numeric
Time
Constructors
RFC822Format | |
ISO8601Format | |
BasicFormat | |
AWSFormat | |
POSIXFormat |
data Time :: Format -> * where Source
Constructors
Time :: UTCTime -> Time a | |
LocaleTime :: TimeLocale -> UTCTime -> Time a |
Instances
_Time :: Iso' (Time a) UTCTime Source
This is a poorly behaved isomorphism, due to the fact LocaleTime
only
exists for testing purposes, and we wish to compose using mapping
in actual usage.
See: convert
.
data UTCTime :: *
This is the simplest representation of UTC. It consists of the day number, and a time offset from midnight. Note that if a day has a leap second added to it, it will have 86401 seconds.
type RFC822 = Time RFC822Format Source
type ISO8601 = Time ISO8601Format Source
type BasicTime = Time BasicFormat Source
type POSIX = Time POSIXFormat Source
Sensitive
Constructors
Sensitive | |
Fields
|
Instances
Eq a => Eq (Sensitive a) | |
Ord a => Ord (Sensitive a) | |
Show (Sensitive a) | |
IsString a => IsString (Sensitive a) | |
ToJSON a => ToJSON (Sensitive a) | |
FromJSON a => FromJSON (Sensitive a) | |
Monoid a => Monoid (Sensitive a) | |
ToText a => ToText (Sensitive a) | |
FromText a => FromText (Sensitive a) | |
ToByteString a => ToByteString (Sensitive a) | |
ToQuery a => ToQuery (Sensitive a) | |
ToXML a => ToXML (Sensitive a) | |
FromXML a => FromXML (Sensitive a) |
_Sensitive :: Iso' (Sensitive a) a Source
HTTP
Body
Constructors
RsBody (ResumableSource (ResourceT IO) ByteString) |
connectBody :: MonadResource m => RsBody -> Sink ByteString m a -> m a Source
bodyHash :: RqBody -> ByteString Source
Minimal complete definition
Nothing
Instances
sourceBody :: Digest SHA256 -> Int64 -> Source IO ByteString -> RqBody Source
sourceFileIO :: MonadIO m => FilePath -> m RqBody Source
sourcePopper :: Source IO ByteString -> GivesPopper () Source
Headers
(~:) :: FromText a => ResponseHeaders -> HeaderName -> Either String a Source
(~:?) :: FromText a => ResponseHeaders -> HeaderName -> Either String (Maybe a) Source
(=:) :: ToHeader a => HeaderName -> a -> [Header] Source
hdr :: HeaderName -> ByteString -> [Header] -> [Header] Source
toHeaderText :: ToText a => HeaderName -> a -> [Header] Source
Minimal complete definition
Nothing
Methods
toHeader :: HeaderName -> a -> [Header] Source
Instances
ToHeader ByteString | |
ToHeader Text | |
ToByteString a => ToHeader (Maybe a) | |
(ToByteString k, ToByteString v) => ToHeader (HashMap k v) | |
ToHeader (Map (CI Text) Text) |
Path
Minimal complete definition
Nothing
Query
Minimal complete definition
Nothing
Instances
ToQuery Bool | |
ToQuery Char | |
ToQuery Double | |
ToQuery Int | |
ToQuery Integer | |
ToQuery ByteString | |
ToQuery Text | |
ToQuery Natural | |
ToQuery Query | |
ToQuery Base64 | |
ToQuery Nat | |
ToQuery AWSTime | |
ToQuery BasicTime | |
ToQuery ISO8601 | |
ToQuery RFC822 | |
ToQuery a => ToQuery [a] | |
ToQuery a => ToQuery (Maybe a) | |
ToQuery a => ToQuery (Sensitive a) | |
(ToByteString k, ToByteString v) => ToQuery (k, Maybe v) | |
(ToByteString k, ToQuery v) => ToQuery (k, v) | |
ToQuery a => ToQuery (List1 e a) | |
ToQuery a => ToQuery (List e a) | |
(KnownSymbol e, KnownSymbol i, KnownSymbol j, Eq k, Hashable k, ToQuery k, ToQuery v) => ToQuery (EMap e i j k v) |
renderQuery :: Query -> ByteString Source
(=?) :: ToQuery a => ByteString -> a -> Query Source
URI
XML
FromXML
Instances
FromXML Bool | |
FromXML Double | |
FromXML Int | |
FromXML Integer | |
FromXML Text | |
FromXML Natural | |
FromXML Base64 | |
FromXML Nat | |
FromXML POSIX | |
FromXML AWSTime | |
FromXML BasicTime | |
FromXML ISO8601 | |
FromXML RFC822 | |
FromXML Region | |
FromXML RESTError | |
FromXML ErrorType | |
FromXML a => FromXML (Maybe a) | |
FromXML a => FromXML (Sensitive a) | |
(KnownSymbol e, FromXML a) => FromXML (List1 e a) | |
(KnownSymbol e, FromXML a) => FromXML (List e a) | |
(KnownSymbol e, KnownSymbol i, KnownSymbol j, Eq k, Hashable k, FromXML k, FromXML v) => FromXML (EMap e i j k v) |
ToXML
Minimal complete definition
Nothing
Instances
ToXML Bool | |
ToXML Double | |
ToXML Int | |
ToXML Integer | |
ToXML Text | |
ToXML Natural | |
ToXML Base64 | |
ToXML Nat | |
ToXML POSIX | |
ToXML AWSTime | |
ToXML BasicTime | |
ToXML ISO8601 | |
ToXML RFC822 | |
ToXML Region | |
ToXML a => ToXML (Maybe a) | |
ToXML a => ToXML (Sensitive a) | |
(KnownSymbol e, ToXML a) => ToXML (List1 e a) | |
(KnownSymbol e, ToXML a) => ToXML (List e a) | |
(KnownSymbol e, KnownSymbol i, KnownSymbol j, Eq k, Hashable k, ToXML k, ToXML v) => ToXML (EMap e i j k v) |
encodeXML :: ToXMLRoot a => a -> LazyByteString Source
unsafeToXML :: (Show a, ToXML a) => a -> Node Source
Caution: This is for use with types which are flattened
in
AWS service model terminology. It is applied by the generator/templating
in safe contexts only.
JSON
FromJSON
class FromJSON a where
A type that can be converted from JSON, with the possibility of failure.
When writing an instance, use empty
, mzero
, or fail
to make a
conversion fail, e.g. if an Object
is missing a required key, or
the value is of the wrong type.
An example type and instance:
@{-# LANGUAGE OverloadedStrings #-}
data Coord = Coord { x :: Double, y :: Double }
instance FromJSON Coord where
parseJSON (Object
v) = Coord <$>
v .:
"x" <*>
v .:
"y"
-- A non-Object
value is of the wrong type, so use mzero
to fail.
parseJSON _ = mzero
@
Note the use of the OverloadedStrings
language extension which enables
Text
values to be written as string literals.
Instead of manually writing your FromJSON
instance, there are three options
to do it automatically:
- Data.Aeson.TH provides template-haskell functions which will derive an instance at compile-time. The generated instance is optimized for your type so will probably be more efficient than the following two options:
- Data.Aeson.Generic provides a generic
fromJSON
function that parses to any type which is an instance ofData
. - If your compiler has support for the
DeriveGeneric
andDefaultSignatures
language extensions,parseJSON
will have a default generic implementation.
To use this, simply add a deriving
clause to your datatype and
declare a Generic
FromJSON
instance for your datatype without giving a definition
for parseJSON
.
For example the previous example can be simplified to just:
@{-# LANGUAGE DeriveGeneric #-}
import GHC.Generics
data Coord = Coord { x :: Double, y :: Double } deriving Generic
instance FromJSON Coord @
Note that, instead of using DefaultSignatures
, it's also possible
to parameterize the generic decoding using genericParseJSON
applied
to your encoding/decoding Options
:
instance FromJSON Coord where parseJSON =genericParseJSON
defaultOptions
Minimal complete definition
Nothing
Instances
Parser a
withObject :: String -> (Object -> Parser a) -> Value -> Parser a
withObject expected f value
applies f
to the Object
when value
is an Object
and fails using
otherwise.typeMismatch
expected
(.:) :: FromJSON a => Object -> Text -> Parser a
Retrieve the value associated with the given key of an Object
.
The result is empty
if the key is not present or the value cannot
be converted to the desired type.
This accessor is appropriate if the key and value must be present in an object for it to be valid. If the key and value are optional, use '(.:?)' instead.
(.:?) :: FromJSON a => Object -> Text -> Parser (Maybe a)
Retrieve the value associated with the given key of an Object
.
The result is Nothing
if the key is not present, or empty
if
the value cannot be converted to the desired type.
This accessor is most useful if the key and value can be absent from an object without affecting its validity. If the key and value are mandatory, use '(.:)' instead.
Either String a
ToJSON
class ToJSON a where
A type that can be converted to JSON.
An example type and instance:
@{-# LANGUAGE OverloadedStrings #-}
data Coord = Coord { x :: Double, y :: Double }
instance ToJSON Coord where
toJSON (Coord x y) = object
["x" .=
x, "y" .=
y]
@
Note the use of the OverloadedStrings
language extension which enables
Text
values to be written as string literals.
Instead of manually writing your ToJSON
instance, there are three options
to do it automatically:
- Data.Aeson.TH provides template-haskell functions which will derive an instance at compile-time. The generated instance is optimized for your type so will probably be more efficient than the following two options:
- Data.Aeson.Generic provides a generic
toJSON
function that accepts any type which is an instance ofData
. - If your compiler has support for the
DeriveGeneric
andDefaultSignatures
language extensions (GHC 7.2 and newer),toJSON
will have a default generic implementation.
To use the latter option, simply add a deriving
clause to your
datatype and declare a Generic
ToJSON
instance for your datatype without giving a
definition for toJSON
.
For example the previous example can be simplified to just:
@{-# LANGUAGE DeriveGeneric #-}
import GHC.Generics
data Coord = Coord { x :: Double, y :: Double } deriving Generic
instance ToJSON Coord @
Note that, instead of using DefaultSignatures
, it's also possible
to parameterize the generic encoding using genericToJSON
applied
to your encoding/decoding Options
:
instance ToJSON Coord where toJSON =genericToJSON
defaultOptions
Minimal complete definition
Nothing
Instances
toJSONText :: ToText a => a -> Value Source
Collections
Instances
IsList (List e a) | |
Eq a => Eq (List e a) | |
Ord a => Ord (List e a) | |
Show a => Show (List e a) | |
ToJSON a => ToJSON (List e a) | |
FromJSON a => FromJSON (List e a) | |
Monoid (List e a) | |
Semigroup (List e a) | |
ToQuery a => ToQuery (List e a) | |
(KnownSymbol e, ToXML a) => ToXML (List e a) | |
(KnownSymbol e, FromXML a) => FromXML (List e a) | |
type Item (List e a) = a |
Instances
Functor (List1 e) | |
Foldable (List1 e) | |
Traversable (List1 e) | |
Eq a => Eq (List1 e a) | |
Ord a => Ord (List1 e a) | |
Show a => Show (List1 e a) | |
ToJSON a => ToJSON (List1 e a) | |
FromJSON a => FromJSON (List1 e a) | |
Semigroup (List1 e a) | |
ToQuery a => ToQuery (List1 e a) | |
(KnownSymbol e, ToXML a) => ToXML (List1 e a) | |
(KnownSymbol e, FromXML a) => FromXML (List1 e a) |
Instances
(Eq k, Hashable k) => IsList (Map k v) | |
(Eq k, Eq v) => Eq (Map k v) | |
(Show k, Show v) => Show (Map k v) | |
(Eq k, Hashable k, ToText k, ToJSON v) => ToJSON (Map k v) | |
(Eq k, Hashable k, FromText k, FromJSON v) => FromJSON (Map k v) | |
(Eq k, Hashable k) => Monoid (Map k v) | |
(Eq k, Hashable k) => Semigroup (Map k v) | |
ToHeader (Map (CI Text) Text) | |
type Item (Map k v) = (k, v) |
Instances
(Eq k, Hashable k) => IsList (EMap e i j k v) | |
(Eq k, Eq v) => Eq (EMap e i j k v) | |
(Show k, Show v) => Show (EMap e i j k v) | |
(Eq k, Hashable k) => Monoid (EMap e i j k v) | |
(Eq k, Hashable k) => Semigroup (EMap e i j k v) | |
(KnownSymbol e, KnownSymbol i, KnownSymbol j, Eq k, Hashable k, ToQuery k, ToQuery v) => ToQuery (EMap e i j k v) | |
(KnownSymbol e, KnownSymbol i, KnownSymbol j, Eq k, Hashable k, ToXML k, ToXML v) => ToXML (EMap e i j k v) | |
(KnownSymbol e, KnownSymbol i, KnownSymbol j, Eq k, Hashable k, FromXML k, FromXML v) => FromXML (EMap e i j k v) | |
type Item (EMap e i j k v) = (k, v) |