| 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
- class ToBuilder a where
- showBS :: ToByteString a => a -> String
- buildBS :: ToBuilder a => a -> LazyByteString
- stripBS :: ByteString -> ByteString
- data Base64
- class FromText a where
- fromText :: FromText a => Text -> Either String a
- takeLowerText :: 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 :: 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
- isStreaming :: RqBody -> Bool
- class ToBody a where
- (~:) :: 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)
- (=?) :: ToQuery a => ByteString -> a -> Query
- pair :: ToQuery a => ByteString -> a -> Query -> Query
- toQueryList :: (IsList a, ToQuery (Item a)) => ByteString -> a -> Query
- collapsePath :: 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 -> [Node] -> Either String (Maybe Text)
- withElement :: Text -> ([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)
- (.!@) :: Either String (Maybe a) -> a -> Either String a
- class ToXML a where
- class ToXMLRoot a where
- encodeXML :: ToXMLRoot a => a -> LazyByteString
- toXMLText :: ToText a => a -> [Node]
- namespaced :: Text -> Text -> [Node] -> Maybe Element
- element :: Name -> [Node] -> Element
- nodes :: Name -> [Node] -> [Node]
- (=@) :: ToXML a => Name -> a -> Node
- extractRoot :: Text -> [Node] -> Maybe Element
- unsafeToXML :: (Show a, ToXML a) => a -> Node
- class FromJSON a where
- parseJSONText :: FromText a => String -> Value -> Parser a
- eitherDecode' :: FromJSON a => ByteString -> Either String a
- withObject :: String -> (Object -> Parser a) -> Value -> Parser a
- (.:) :: FromJSON a => Object -> Text -> Parser a
- (.:?) :: FromJSON a => Object -> Text -> Parser (Maybe a)
- (.!=) :: Parser (Maybe a) -> a -> Parser 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
class ToBuilder a where Source
Minimal complete definition
Nothing
Instances
showBS :: ToByteString a => a -> String Source
buildBS :: ToBuilder a => a -> LazyByteString Source
stripBS :: ByteString -> ByteString Source
Base64 encoded binary data.
Instances
Text
Instances
Instances
| ToText Bool Source | |
| ToText Double Source | |
| ToText Int Source | |
| ToText Int64 Source | |
| ToText Integer Source | |
| ToText ByteString Source | |
| ToText Scientific Source | |
| ToText Text Source | |
| ToText Natural Source | |
| ToText StdMethod Source | |
| ToText Query Source | |
| ToText Base64 Source | |
| ToText Nat Source | |
| ToText POSIX Source | |
| ToText AWSTime Source | |
| ToText BasicTime Source | |
| ToText ISO8601 Source | |
| ToText RFC822 Source | |
| ToText Action Source | |
| ToText Region Source | |
| ToText SecurityToken Source | |
| ToText SecretKey Source | |
| ToText AccessKey Source | |
| ToText a => ToText [a] Source | |
| ToText a => ToText (CI a) Source | |
| ToText (Digest a) Source | |
| ToText (Response a) Source | |
| ToText a => ToText (Sensitive a) Source | |
| (ToText a, ToText b) => ToText (a, b) Source |
Numeric
Time
Constructors
| RFC822Format | |
| ISO8601Format | |
| BasicFormat | |
| AWSFormat | |
| POSIXFormat |
data Time :: Format -> * where Source
Instances
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
read . show /= isomorphic
Constructors
| Sensitive | |
Fields
| |
Instances
| Eq a => Eq (Sensitive a) Source | |
| Ord a => Ord (Sensitive a) Source | |
| Read a => Read (Sensitive a) Source | |
| Show (Sensitive a) Source | |
| IsString a => IsString (Sensitive a) Source | |
| ToJSON a => ToJSON (Sensitive a) Source | |
| FromJSON a => FromJSON (Sensitive a) Source | |
| Monoid a => Monoid (Sensitive a) Source | |
| ToText a => ToText (Sensitive a) Source | |
| FromText a => FromText (Sensitive a) Source | |
| ToByteString a => ToByteString (Sensitive a) Source | |
| ToQuery a => ToQuery (Sensitive a) Source | |
| ToXML a => ToXML (Sensitive a) Source | |
| FromXML a => FromXML (Sensitive a) Source |
_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
isStreaming :: RqBody -> Bool Source
Minimal complete definition
Nothing
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
Path
Minimal complete definition
Nothing
Query
Minimal complete definition
Nothing
Instances
| ToQuery Bool Source | |
| ToQuery Char Source | |
| ToQuery Double Source | |
| ToQuery Int Source | |
| ToQuery Integer Source | |
| ToQuery ByteString Source | |
| ToQuery Text Source | |
| ToQuery Natural Source | |
| ToQuery Query Source | |
| ToQuery Base64 Source | |
| ToQuery Nat Source | |
| ToQuery AWSTime Source | |
| ToQuery BasicTime Source | |
| ToQuery ISO8601 Source | |
| ToQuery RFC822 Source | |
| ToQuery a => ToQuery [a] Source | |
| ToQuery a => ToQuery (Maybe a) Source | |
| ToQuery a => ToQuery (Sensitive a) Source | |
| (ToByteString k, ToQuery v) => ToQuery (k, v) Source | |
| (KnownSymbol e, ToQuery a) => ToQuery (List1 e a) Source | |
| (KnownSymbol e, ToQuery a) => ToQuery (List e a) Source | |
| (KnownSymbol e, KnownSymbol i, KnownSymbol j, Eq k, Hashable k, ToQuery k, ToQuery v) => ToQuery (EMap e i j k v) Source |
renderQuery :: Query -> ByteString Source
(=?) :: ToQuery a => ByteString -> a -> Query Source
toQueryList :: (IsList a, ToQuery (Item a)) => ByteString -> a -> Query Source
URI
XML
FromXML
Instances
| FromXML Bool Source | |
| FromXML Double Source | |
| FromXML Int Source | |
| FromXML Integer Source | |
| FromXML Text Source | |
| FromXML Natural Source | |
| FromXML Base64 Source | |
| FromXML Nat Source | |
| FromXML POSIX Source | |
| FromXML AWSTime Source | |
| FromXML BasicTime Source | |
| FromXML ISO8601 Source | |
| FromXML RFC822 Source | |
| FromXML Region Source | |
| FromXML RESTError Source | |
| FromXML ErrorType Source | |
| FromXML ErrorCode Source | |
| FromXML a => FromXML (Maybe a) Source | |
| FromXML a => FromXML (Sensitive a) Source | |
| (KnownSymbol e, FromXML a) => FromXML (List1 e a) Source | |
| (KnownSymbol e, FromXML a) => FromXML (List e a) Source | |
| (KnownSymbol e, KnownSymbol i, KnownSymbol j, Eq k, Hashable k, FromXML k, FromXML v) => FromXML (EMap e i j k v) Source |
ToXML
Minimal complete definition
Nothing
Instances
| ToXML Bool Source | |
| ToXML Double Source | |
| ToXML Int Source | |
| ToXML Integer Source | |
| ToXML Text Source | |
| ToXML Natural Source | |
| ToXML Base64 Source | |
| ToXML Nat Source | |
| ToXML POSIX Source | |
| ToXML AWSTime Source | |
| ToXML BasicTime Source | |
| ToXML ISO8601 Source | |
| ToXML RFC822 Source | |
| ToXML Region Source | |
| ToXML a => ToXML (Maybe a) Source | |
| ToXML a => ToXML (Sensitive a) Source | |
| (KnownSymbol e, ToXML a) => ToXML (List1 e a) Source | |
| (KnownSymbol e, ToXML a) => ToXML (List e a) Source | |
| (KnownSymbol e, KnownSymbol i, KnownSymbol j, Eq k, Hashable k, ToXML k, ToXML v) => ToXML (EMap e i j k v) Source |
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
fromJSONfunction that parses to any type which is an instance ofData. - If your compiler has support for the
DeriveGenericandDefaultSignatureslanguage extensions,parseJSONwill have a default generic implementation.
To use this, simply add a deriving clause to your datatype and
declare a GenericFromJSON 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
| FromJSON Base64 | |
| FromJSON Nat | |
| FromJSON POSIX | |
| FromJSON AWSTime | |
| FromJSON BasicTime | |
| FromJSON ISO8601 | |
| FromJSON RFC822 | |
| FromJSON AuthEnv | |
| FromJSON ErrorCode | |
| FromJSON JSONError | |
| FromJSON a => FromJSON (Sensitive a) | |
| FromJSON a => FromJSON (List1 e a) | |
| FromJSON a => FromJSON (List e a) | |
| (Eq k, Hashable k, FromText k, FromJSON v) => FromJSON (Map k v) |
eitherDecode' :: FromJSON a => ByteString -> Either String a
Like decode' but returns an error message when decoding fails.
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.
(.!=) :: Parser (Maybe a) -> a -> Parser a
Helper for use in combination with .:? to provide default
values for optional JSON object fields.
This combinator is most useful if the key and value can be absent from an object without affecting its validity and we know a default value to assign in that case. If the key and value are mandatory, use '(.:)' instead.
Example usage:
v1 <- o.:?"opt_field_with_dfl" .!= "default_val" v2 <- o.:"mandatory_field" v3 <- o.:?"opt_field2"
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
toJSONfunction that accepts any type which is an instance ofData. - If your compiler has support for the
DeriveGenericandDefaultSignatureslanguage extensions (GHC 7.2 and newer),toJSONwill have a default generic implementation.
To use the latter option, simply add a deriving clause to your
datatype and declare a GenericToJSON 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
toJSONText :: ToText a => a -> Value Source
Collections
Instances
| IsList (List e a) Source | |
| Eq a => Eq (List e a) Source | |
| Ord a => Ord (List e a) Source | |
| Read a => Read (List e a) Source | |
| Show a => Show (List e a) Source | |
| ToJSON a => ToJSON (List e a) Source | |
| FromJSON a => FromJSON (List e a) Source | |
| Monoid (List e a) Source | |
| Semigroup (List e a) Source | |
| (KnownSymbol e, ToQuery a) => ToQuery (List e a) Source | |
| (KnownSymbol e, ToXML a) => ToXML (List e a) Source | |
| (KnownSymbol e, FromXML a) => FromXML (List e a) Source | |
| type Item (List e a) = a Source |
Instances
| Functor (List1 e) Source | |
| Foldable (List1 e) Source | |
| Traversable (List1 e) Source | |
| Eq a => Eq (List1 e a) Source | |
| Ord a => Ord (List1 e a) Source | |
| Read a => Read (List1 e a) Source | |
| Show a => Show (List1 e a) Source | |
| ToJSON a => ToJSON (List1 e a) Source | |
| FromJSON a => FromJSON (List1 e a) Source | |
| Semigroup (List1 e a) Source | |
| (KnownSymbol e, ToQuery a) => ToQuery (List1 e a) Source | |
| (KnownSymbol e, ToXML a) => ToXML (List1 e a) Source | |
| (KnownSymbol e, FromXML a) => FromXML (List1 e a) Source |
Instances
| (Eq k, Hashable k) => IsList (Map k v) Source | |
| (Eq k, Eq v) => Eq (Map k v) Source | |
| (Eq k, Read k, Read v, Hashable k) => Read (Map k v) Source | |
| (Show k, Show v) => Show (Map k v) Source | |
| (Eq k, Hashable k, ToText k, ToJSON v) => ToJSON (Map k v) Source | |
| (Eq k, Hashable k, FromText k, FromJSON v) => FromJSON (Map k v) Source | |
| (Eq k, Hashable k) => Monoid (Map k v) Source | |
| (Eq k, Hashable k) => Semigroup (Map k v) Source | |
| ToHeader (Map (CI Text) Text) Source | |
| type Item (Map k v) = (k, v) Source |
Instances
| (Eq k, Hashable k) => IsList (EMap e i j k v) Source | |
| (Eq k, Eq v) => Eq (EMap e i j k v) Source | |
| (Eq k, Read k, Read v, Hashable k) => Read (EMap e i j k v) Source | |
| (Show k, Show v) => Show (EMap e i j k v) Source | |
| (Eq k, Hashable k) => Monoid (EMap e i j k v) Source | |
| (Eq k, Hashable k) => Semigroup (EMap e i j k v) Source | |
| (KnownSymbol e, KnownSymbol i, KnownSymbol j, Eq k, Hashable k, ToQuery k, ToQuery v) => ToQuery (EMap e i j k v) Source | |
| (KnownSymbol e, KnownSymbol i, KnownSymbol j, Eq k, Hashable k, ToXML k, ToXML v) => ToXML (EMap e i j k v) Source | |
| (KnownSymbol e, KnownSymbol i, KnownSymbol j, Eq k, Hashable k, FromXML k, FromXML v) => FromXML (EMap e i j k v) Source | |
| type Item (EMap e i j k v) = (k, v) Source |