amazonka-core-0.3.1: Core functionality and data types for Amazonka libraries.

Safe HaskellNone
LanguageHaskell2010

Network.AWS.Data

Contents

Description

Serialisation classes and primitives for the various formats used to communicate with AWS.

Synopsis

ByteString

Text

matchCI :: Text -> a -> Parser a Source

Numeric

Time

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.

Sensitive

HTTP

Body

class ToBody a where Source

Minimal complete definition

Nothing

Methods

toBody :: a -> RqBody Source

Headers

class ToHeaders a where Source

Minimal complete definition

Nothing

Methods

toHeaders :: a -> [Header] Source

hdrs :: [Header] -> [Header] -> [Header] Source

class ToHeader a where Source

Minimal complete definition

Nothing

Methods

toHeader :: HeaderName -> a -> [Header] Source

Path

class ToPath a where Source

Minimal complete definition

Nothing

Methods

toPath :: a -> Text Source

Instances

Query

URI

XML

FromXML

ToXML

class ToXMLRoot a where Source

Methods

toXMLRoot :: a -> Maybe Element Source

toXMLText :: ToText a => a -> [Node] Source

nodes :: Name -> [Node] -> [Node] Source

(=@) :: ToXML a => Name -> a -> Node 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 of Data.
  • If your compiler has support for the DeriveGeneric and DefaultSignatures language extensions, parseJSON will have a default generic implementation.

To use this, simply add a deriving Generic clause to your datatype and declare a 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

Methods

parseJSON :: Value -> Parser a

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 typeMismatch expected otherwise.

(.:) :: 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 toJSON function that accepts any type which is an instance of Data.
  • If your compiler has support for the DeriveGeneric and DefaultSignatures language extensions (GHC 7.2 and newer), toJSON will have a default generic implementation.

To use the latter option, simply add a deriving Generic clause to your datatype and declare a 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

Methods

toJSON :: a -> Value

object :: [Pair] -> Value

Create a Value from a list of name/value Pairs. If duplicate keys arise, earlier keys and their associated values win.

(.=) :: ToJSON a => Text -> a -> Pair

Construct a Pair from a key and a value.

Collections

newtype List e a Source

Constructors

List 

Fields

list :: [a]
 

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 

newtype List1 e a Source

Constructors

List1 

Fields

list1 :: NonEmpty a
 

Instances

_List :: (Coercible a b, Coercible b a) => Iso' (List e a) [b] Source

_List1 :: (Coercible a b, Coercible b a) => Iso' (List1 e a) (NonEmpty b) Source

fromList1 :: List1 e a -> List e a Source

newtype Map k v Source

Constructors

Map 

Fields

fromMap :: HashMap k v
 

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 

_Map :: (Coercible a b, Coercible b a) => Iso' (Map k a) (HashMap k b) Source

newtype EMap e i j k v Source

Constructors

EMap 

Fields

fromEMap :: HashMap k v
 

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 

_EMap :: (Coercible a b, Coercible b a) => Iso' (EMap e i j k a) (HashMap k b) Source