{-# LANGUAGE DeriveGeneric              #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TypeFamilies               #-}

module Aws.DynamoDb.Commands.Table
    ( -- * Commands
      CreateTable(..)
    , createTable
    , CreateTableResult(..)
    , DescribeTable(..)
    , DescribeTableResult(..)
    , UpdateTable(..)
    , UpdateTableResult(..)
    , DeleteTable(..)
    , DeleteTableResult(..)
    , ListTables(..)
    , ListTablesResult(..)

    -- * Data passed in the commands
    , AttributeType(..)
    , AttributeDefinition(..)
    , KeySchema(..)
    , Projection(..)
    , LocalSecondaryIndex(..)
    , LocalSecondaryIndexStatus(..)
    , ProvisionedThroughput(..)
    , ProvisionedThroughputStatus(..)
    , GlobalSecondaryIndex(..)
    , GlobalSecondaryIndexStatus(..)
    , GlobalSecondaryIndexUpdate(..)
    , TableDescription(..)
    ) where

-------------------------------------------------------------------------------
import           Control.Applicative
import           Data.Aeson            ((.!=), (.:), (.:?), (.=))
import qualified Data.Aeson            as A
import qualified Data.Aeson.KeyMap     as KM
import qualified Data.Aeson.Types      as A
import           Data.Char             (toUpper)
import           Data.Scientific       (Scientific)
import qualified Data.Text             as T
import           Data.Time
import           Data.Time.Clock.POSIX
import           Data.Typeable
import qualified Data.Vector           as V
import           GHC.Generics          (Generic)
import           Prelude
-------------------------------------------------------------------------------
import           Aws.Core
import           Aws.DynamoDb.Core
-------------------------------------------------------------------------------


capitalizeOpt :: A.Options
capitalizeOpt :: Options
capitalizeOpt = Options
A.defaultOptions
    { A.fieldLabelModifier = \String
x -> case String
x of
                                     (Char
c:String
cs) -> Char -> Char
toUpper Char
c Char -> String -> String
forall a. a -> [a] -> [a]
: String
cs
                                     [] -> []
    }


dropOpt :: Int -> A.Options
dropOpt :: Int -> Options
dropOpt Int
d = Options
A.defaultOptions { A.fieldLabelModifier = drop d }


convertToUTCTime :: Scientific -> UTCTime
convertToUTCTime :: Scientific -> UTCTime
convertToUTCTime = POSIXTime -> UTCTime
posixSecondsToUTCTime (POSIXTime -> UTCTime)
-> (Scientific -> POSIXTime) -> Scientific -> UTCTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> POSIXTime
forall a. Num a => Integer -> a
fromInteger (Integer -> POSIXTime)
-> (Scientific -> Integer) -> Scientific -> POSIXTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Scientific -> Integer
forall b. Integral b => Scientific -> b
forall a b. (RealFrac a, Integral b) => a -> b
round


-- | The type of a key attribute that appears in the table key or as a
-- key in one of the indices.
data AttributeType = AttrString | AttrNumber | AttrBinary
    deriving (Int -> AttributeType -> String -> String
[AttributeType] -> String -> String
AttributeType -> String
(Int -> AttributeType -> String -> String)
-> (AttributeType -> String)
-> ([AttributeType] -> String -> String)
-> Show AttributeType
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> AttributeType -> String -> String
showsPrec :: Int -> AttributeType -> String -> String
$cshow :: AttributeType -> String
show :: AttributeType -> String
$cshowList :: [AttributeType] -> String -> String
showList :: [AttributeType] -> String -> String
Show, ReadPrec [AttributeType]
ReadPrec AttributeType
Int -> ReadS AttributeType
ReadS [AttributeType]
(Int -> ReadS AttributeType)
-> ReadS [AttributeType]
-> ReadPrec AttributeType
-> ReadPrec [AttributeType]
-> Read AttributeType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AttributeType
readsPrec :: Int -> ReadS AttributeType
$creadList :: ReadS [AttributeType]
readList :: ReadS [AttributeType]
$creadPrec :: ReadPrec AttributeType
readPrec :: ReadPrec AttributeType
$creadListPrec :: ReadPrec [AttributeType]
readListPrec :: ReadPrec [AttributeType]
Read, Eq AttributeType
Eq AttributeType =>
(AttributeType -> AttributeType -> Ordering)
-> (AttributeType -> AttributeType -> Bool)
-> (AttributeType -> AttributeType -> Bool)
-> (AttributeType -> AttributeType -> Bool)
-> (AttributeType -> AttributeType -> Bool)
-> (AttributeType -> AttributeType -> AttributeType)
-> (AttributeType -> AttributeType -> AttributeType)
-> Ord AttributeType
AttributeType -> AttributeType -> Bool
AttributeType -> AttributeType -> Ordering
AttributeType -> AttributeType -> AttributeType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AttributeType -> AttributeType -> Ordering
compare :: AttributeType -> AttributeType -> Ordering
$c< :: AttributeType -> AttributeType -> Bool
< :: AttributeType -> AttributeType -> Bool
$c<= :: AttributeType -> AttributeType -> Bool
<= :: AttributeType -> AttributeType -> Bool
$c> :: AttributeType -> AttributeType -> Bool
> :: AttributeType -> AttributeType -> Bool
$c>= :: AttributeType -> AttributeType -> Bool
>= :: AttributeType -> AttributeType -> Bool
$cmax :: AttributeType -> AttributeType -> AttributeType
max :: AttributeType -> AttributeType -> AttributeType
$cmin :: AttributeType -> AttributeType -> AttributeType
min :: AttributeType -> AttributeType -> AttributeType
Ord, Typeable, AttributeType -> AttributeType -> Bool
(AttributeType -> AttributeType -> Bool)
-> (AttributeType -> AttributeType -> Bool) -> Eq AttributeType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AttributeType -> AttributeType -> Bool
== :: AttributeType -> AttributeType -> Bool
$c/= :: AttributeType -> AttributeType -> Bool
/= :: AttributeType -> AttributeType -> Bool
Eq, Int -> AttributeType
AttributeType -> Int
AttributeType -> [AttributeType]
AttributeType -> AttributeType
AttributeType -> AttributeType -> [AttributeType]
AttributeType -> AttributeType -> AttributeType -> [AttributeType]
(AttributeType -> AttributeType)
-> (AttributeType -> AttributeType)
-> (Int -> AttributeType)
-> (AttributeType -> Int)
-> (AttributeType -> [AttributeType])
-> (AttributeType -> AttributeType -> [AttributeType])
-> (AttributeType -> AttributeType -> [AttributeType])
-> (AttributeType
    -> AttributeType -> AttributeType -> [AttributeType])
-> Enum AttributeType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: AttributeType -> AttributeType
succ :: AttributeType -> AttributeType
$cpred :: AttributeType -> AttributeType
pred :: AttributeType -> AttributeType
$ctoEnum :: Int -> AttributeType
toEnum :: Int -> AttributeType
$cfromEnum :: AttributeType -> Int
fromEnum :: AttributeType -> Int
$cenumFrom :: AttributeType -> [AttributeType]
enumFrom :: AttributeType -> [AttributeType]
$cenumFromThen :: AttributeType -> AttributeType -> [AttributeType]
enumFromThen :: AttributeType -> AttributeType -> [AttributeType]
$cenumFromTo :: AttributeType -> AttributeType -> [AttributeType]
enumFromTo :: AttributeType -> AttributeType -> [AttributeType]
$cenumFromThenTo :: AttributeType -> AttributeType -> AttributeType -> [AttributeType]
enumFromThenTo :: AttributeType -> AttributeType -> AttributeType -> [AttributeType]
Enum, AttributeType
AttributeType -> AttributeType -> Bounded AttributeType
forall a. a -> a -> Bounded a
$cminBound :: AttributeType
minBound :: AttributeType
$cmaxBound :: AttributeType
maxBound :: AttributeType
Bounded, (forall x. AttributeType -> Rep AttributeType x)
-> (forall x. Rep AttributeType x -> AttributeType)
-> Generic AttributeType
forall x. Rep AttributeType x -> AttributeType
forall x. AttributeType -> Rep AttributeType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AttributeType -> Rep AttributeType x
from :: forall x. AttributeType -> Rep AttributeType x
$cto :: forall x. Rep AttributeType x -> AttributeType
to :: forall x. Rep AttributeType x -> AttributeType
Generic)

instance A.ToJSON AttributeType where
    toJSON :: AttributeType -> Value
toJSON AttributeType
AttrString = Text -> Value
A.String Text
"S"
    toJSON AttributeType
AttrNumber = Text -> Value
A.String Text
"N"
    toJSON AttributeType
AttrBinary = Text -> Value
A.String Text
"B"

instance A.FromJSON AttributeType where
    parseJSON :: Value -> Parser AttributeType
parseJSON (A.String Text
str) =
        case Text
str of
            Text
"S" -> AttributeType -> Parser AttributeType
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return AttributeType
AttrString
            Text
"N" -> AttributeType -> Parser AttributeType
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return AttributeType
AttrNumber
            Text
"B" -> AttributeType -> Parser AttributeType
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return AttributeType
AttrBinary
            Text
_   -> String -> Parser AttributeType
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser AttributeType) -> String -> Parser AttributeType
forall a b. (a -> b) -> a -> b
$ String
"Invalid attribute type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Text -> String
T.unpack Text
str
    parseJSON Value
_ = String -> Parser AttributeType
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Attribute type must be a string"

-- | A key attribute that appears in the table key or as a key in one of the indices.
data AttributeDefinition = AttributeDefinition {
      AttributeDefinition -> Text
attributeName :: T.Text
    , AttributeDefinition -> AttributeType
attributeType :: AttributeType
    } deriving (AttributeDefinition -> AttributeDefinition -> Bool
(AttributeDefinition -> AttributeDefinition -> Bool)
-> (AttributeDefinition -> AttributeDefinition -> Bool)
-> Eq AttributeDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AttributeDefinition -> AttributeDefinition -> Bool
== :: AttributeDefinition -> AttributeDefinition -> Bool
$c/= :: AttributeDefinition -> AttributeDefinition -> Bool
/= :: AttributeDefinition -> AttributeDefinition -> Bool
Eq,ReadPrec [AttributeDefinition]
ReadPrec AttributeDefinition
Int -> ReadS AttributeDefinition
ReadS [AttributeDefinition]
(Int -> ReadS AttributeDefinition)
-> ReadS [AttributeDefinition]
-> ReadPrec AttributeDefinition
-> ReadPrec [AttributeDefinition]
-> Read AttributeDefinition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AttributeDefinition
readsPrec :: Int -> ReadS AttributeDefinition
$creadList :: ReadS [AttributeDefinition]
readList :: ReadS [AttributeDefinition]
$creadPrec :: ReadPrec AttributeDefinition
readPrec :: ReadPrec AttributeDefinition
$creadListPrec :: ReadPrec [AttributeDefinition]
readListPrec :: ReadPrec [AttributeDefinition]
Read,Eq AttributeDefinition
Eq AttributeDefinition =>
(AttributeDefinition -> AttributeDefinition -> Ordering)
-> (AttributeDefinition -> AttributeDefinition -> Bool)
-> (AttributeDefinition -> AttributeDefinition -> Bool)
-> (AttributeDefinition -> AttributeDefinition -> Bool)
-> (AttributeDefinition -> AttributeDefinition -> Bool)
-> (AttributeDefinition
    -> AttributeDefinition -> AttributeDefinition)
-> (AttributeDefinition
    -> AttributeDefinition -> AttributeDefinition)
-> Ord AttributeDefinition
AttributeDefinition -> AttributeDefinition -> Bool
AttributeDefinition -> AttributeDefinition -> Ordering
AttributeDefinition -> AttributeDefinition -> AttributeDefinition
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AttributeDefinition -> AttributeDefinition -> Ordering
compare :: AttributeDefinition -> AttributeDefinition -> Ordering
$c< :: AttributeDefinition -> AttributeDefinition -> Bool
< :: AttributeDefinition -> AttributeDefinition -> Bool
$c<= :: AttributeDefinition -> AttributeDefinition -> Bool
<= :: AttributeDefinition -> AttributeDefinition -> Bool
$c> :: AttributeDefinition -> AttributeDefinition -> Bool
> :: AttributeDefinition -> AttributeDefinition -> Bool
$c>= :: AttributeDefinition -> AttributeDefinition -> Bool
>= :: AttributeDefinition -> AttributeDefinition -> Bool
$cmax :: AttributeDefinition -> AttributeDefinition -> AttributeDefinition
max :: AttributeDefinition -> AttributeDefinition -> AttributeDefinition
$cmin :: AttributeDefinition -> AttributeDefinition -> AttributeDefinition
min :: AttributeDefinition -> AttributeDefinition -> AttributeDefinition
Ord,Int -> AttributeDefinition -> String -> String
[AttributeDefinition] -> String -> String
AttributeDefinition -> String
(Int -> AttributeDefinition -> String -> String)
-> (AttributeDefinition -> String)
-> ([AttributeDefinition] -> String -> String)
-> Show AttributeDefinition
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> AttributeDefinition -> String -> String
showsPrec :: Int -> AttributeDefinition -> String -> String
$cshow :: AttributeDefinition -> String
show :: AttributeDefinition -> String
$cshowList :: [AttributeDefinition] -> String -> String
showList :: [AttributeDefinition] -> String -> String
Show,Typeable,(forall x. AttributeDefinition -> Rep AttributeDefinition x)
-> (forall x. Rep AttributeDefinition x -> AttributeDefinition)
-> Generic AttributeDefinition
forall x. Rep AttributeDefinition x -> AttributeDefinition
forall x. AttributeDefinition -> Rep AttributeDefinition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AttributeDefinition -> Rep AttributeDefinition x
from :: forall x. AttributeDefinition -> Rep AttributeDefinition x
$cto :: forall x. Rep AttributeDefinition x -> AttributeDefinition
to :: forall x. Rep AttributeDefinition x -> AttributeDefinition
Generic)

instance A.ToJSON AttributeDefinition where
    toJSON :: AttributeDefinition -> Value
toJSON = Options -> AttributeDefinition -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
A.genericToJSON Options
capitalizeOpt

instance A.FromJSON AttributeDefinition where
    parseJSON :: Value -> Parser AttributeDefinition
parseJSON = Options -> Value -> Parser AttributeDefinition
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
A.genericParseJSON Options
capitalizeOpt

-- | The key schema can either be a hash of a single attribute name or a hash attribute name
-- and a range attribute name.
data KeySchema = HashOnly T.Text
               | HashAndRange T.Text T.Text
    deriving (KeySchema -> KeySchema -> Bool
(KeySchema -> KeySchema -> Bool)
-> (KeySchema -> KeySchema -> Bool) -> Eq KeySchema
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: KeySchema -> KeySchema -> Bool
== :: KeySchema -> KeySchema -> Bool
$c/= :: KeySchema -> KeySchema -> Bool
/= :: KeySchema -> KeySchema -> Bool
Eq,ReadPrec [KeySchema]
ReadPrec KeySchema
Int -> ReadS KeySchema
ReadS [KeySchema]
(Int -> ReadS KeySchema)
-> ReadS [KeySchema]
-> ReadPrec KeySchema
-> ReadPrec [KeySchema]
-> Read KeySchema
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS KeySchema
readsPrec :: Int -> ReadS KeySchema
$creadList :: ReadS [KeySchema]
readList :: ReadS [KeySchema]
$creadPrec :: ReadPrec KeySchema
readPrec :: ReadPrec KeySchema
$creadListPrec :: ReadPrec [KeySchema]
readListPrec :: ReadPrec [KeySchema]
Read,Int -> KeySchema -> String -> String
[KeySchema] -> String -> String
KeySchema -> String
(Int -> KeySchema -> String -> String)
-> (KeySchema -> String)
-> ([KeySchema] -> String -> String)
-> Show KeySchema
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> KeySchema -> String -> String
showsPrec :: Int -> KeySchema -> String -> String
$cshow :: KeySchema -> String
show :: KeySchema -> String
$cshowList :: [KeySchema] -> String -> String
showList :: [KeySchema] -> String -> String
Show,Eq KeySchema
Eq KeySchema =>
(KeySchema -> KeySchema -> Ordering)
-> (KeySchema -> KeySchema -> Bool)
-> (KeySchema -> KeySchema -> Bool)
-> (KeySchema -> KeySchema -> Bool)
-> (KeySchema -> KeySchema -> Bool)
-> (KeySchema -> KeySchema -> KeySchema)
-> (KeySchema -> KeySchema -> KeySchema)
-> Ord KeySchema
KeySchema -> KeySchema -> Bool
KeySchema -> KeySchema -> Ordering
KeySchema -> KeySchema -> KeySchema
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: KeySchema -> KeySchema -> Ordering
compare :: KeySchema -> KeySchema -> Ordering
$c< :: KeySchema -> KeySchema -> Bool
< :: KeySchema -> KeySchema -> Bool
$c<= :: KeySchema -> KeySchema -> Bool
<= :: KeySchema -> KeySchema -> Bool
$c> :: KeySchema -> KeySchema -> Bool
> :: KeySchema -> KeySchema -> Bool
$c>= :: KeySchema -> KeySchema -> Bool
>= :: KeySchema -> KeySchema -> Bool
$cmax :: KeySchema -> KeySchema -> KeySchema
max :: KeySchema -> KeySchema -> KeySchema
$cmin :: KeySchema -> KeySchema -> KeySchema
min :: KeySchema -> KeySchema -> KeySchema
Ord,Typeable,(forall x. KeySchema -> Rep KeySchema x)
-> (forall x. Rep KeySchema x -> KeySchema) -> Generic KeySchema
forall x. Rep KeySchema x -> KeySchema
forall x. KeySchema -> Rep KeySchema x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. KeySchema -> Rep KeySchema x
from :: forall x. KeySchema -> Rep KeySchema x
$cto :: forall x. Rep KeySchema x -> KeySchema
to :: forall x. Rep KeySchema x -> KeySchema
Generic)


instance A.ToJSON KeySchema where
    toJSON :: KeySchema -> Value
toJSON (HashOnly Text
a)
        = Array -> Value
A.Array (Array -> Value) -> Array -> Value
forall a b. (a -> b) -> a -> b
$ [Value] -> Array
forall a. [a] -> Vector a
V.fromList [ [Pair] -> Value
A.object [ Key
"AttributeName" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
a
                                          , Key
"KeyType" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= (Text -> Value
A.String Text
"HASH")
                                          ]
                               ]

    toJSON (HashAndRange Text
hash Text
range)
        = Array -> Value
A.Array (Array -> Value) -> Array -> Value
forall a b. (a -> b) -> a -> b
$ [Value] -> Array
forall a. [a] -> Vector a
V.fromList [ [Pair] -> Value
A.object [ Key
"AttributeName" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
hash
                                          , Key
"KeyType" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= (Text -> Value
A.String Text
"HASH")
                                          ]
                               , [Pair] -> Value
A.object [ Key
"AttributeName" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
range
                                          , Key
"KeyType" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= (Text -> Value
A.String Text
"RANGE")
                                          ]
                               ]

instance A.FromJSON KeySchema where
    parseJSON :: Value -> Parser KeySchema
parseJSON (A.Array Array
v) =
        case Array -> Int
forall a. Vector a -> Int
V.length Array
v of
            Int
1 -> do Object
obj <- Value -> Parser Object
forall a. FromJSON a => Value -> Parser a
A.parseJSON (Array
v Array -> Int -> Value
forall a. Vector a -> Int -> a
V.! Int
0)
                    Text
kt <- Object
obj Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"KeyType"
                    if Text
kt Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= (Text
"HASH" :: T.Text)
                        then String -> Parser KeySchema
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"With only one key, the type must be HASH"
                        else Text -> KeySchema
HashOnly (Text -> KeySchema) -> Parser Text -> Parser KeySchema
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"AttributeName"

            Int
2 -> do Object
hash <- Value -> Parser Object
forall a. FromJSON a => Value -> Parser a
A.parseJSON (Array
v Array -> Int -> Value
forall a. Vector a -> Int -> a
V.! Int
0)
                    Object
range <- Value -> Parser Object
forall a. FromJSON a => Value -> Parser a
A.parseJSON (Array
v Array -> Int -> Value
forall a. Vector a -> Int -> a
V.! Int
1)
                    Text
hkt <- Object
hash Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"KeyType"
                    Text
rkt <- Object
range Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"KeyType"
                    if Text
hkt Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= (Text
"HASH" :: T.Text) Bool -> Bool -> Bool
|| Text
rkt Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= (Text
"RANGE" :: T.Text)
                        then String -> Parser KeySchema
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"With two keys, one must be HASH and the other RANGE"
                        else Text -> Text -> KeySchema
HashAndRange (Text -> Text -> KeySchema)
-> Parser Text -> Parser (Text -> KeySchema)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
hash Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"AttributeName"
                                          Parser (Text -> KeySchema) -> Parser Text -> Parser KeySchema
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
range Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"AttributeName"
            Int
_ -> String -> Parser KeySchema
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Key schema must have one or two entries"
    parseJSON Value
_ = String -> Parser KeySchema
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Key schema must be an array"

-- | This determines which attributes are projected into a secondary index.
data Projection = ProjectKeysOnly
                | ProjectAll
                | ProjectInclude [T.Text]
    deriving Int -> Projection -> String -> String
[Projection] -> String -> String
Projection -> String
(Int -> Projection -> String -> String)
-> (Projection -> String)
-> ([Projection] -> String -> String)
-> Show Projection
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> Projection -> String -> String
showsPrec :: Int -> Projection -> String -> String
$cshow :: Projection -> String
show :: Projection -> String
$cshowList :: [Projection] -> String -> String
showList :: [Projection] -> String -> String
Show
instance A.ToJSON Projection where
    toJSON :: Projection -> Value
toJSON Projection
ProjectKeysOnly    = [Pair] -> Value
A.object [ Key
"ProjectionType" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= (Text
"KEYS_ONLY" :: T.Text) ]
    toJSON Projection
ProjectAll         = [Pair] -> Value
A.object [ Key
"ProjectionType" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= (Text
"ALL" :: T.Text) ]
    toJSON (ProjectInclude [Text]
a) = [Pair] -> Value
A.object [ Key
"ProjectionType" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= (Text
"INCLUDE" :: T.Text)
                                         , Key
"NonKeyAttributes" Key -> [Text] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Text]
a
                                         ]
instance A.FromJSON Projection where
    parseJSON :: Value -> Parser Projection
parseJSON (A.Object Object
o) = do
        Text
ty <- (Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"ProjectionType") :: A.Parser T.Text
        case Text
ty of
            Text
"KEYS_ONLY" -> Projection -> Parser Projection
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return Projection
ProjectKeysOnly
            Text
"ALL" -> Projection -> Parser Projection
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return Projection
ProjectAll
            Text
"INCLUDE" -> [Text] -> Projection
ProjectInclude ([Text] -> Projection) -> Parser [Text] -> Parser Projection
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser [Text]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"NonKeyAttributes"
            Text
_ -> String -> Parser Projection
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Invalid projection type"
    parseJSON Value
_ = String -> Parser Projection
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Projection must be an object"

-- | Describes a single local secondary index. The KeySchema MUST
-- share the same hash key attribute as the parent table, only the
-- range key can differ.
data LocalSecondaryIndex
    = LocalSecondaryIndex {
        LocalSecondaryIndex -> Text
localIndexName  :: T.Text
      , LocalSecondaryIndex -> KeySchema
localKeySchema  :: KeySchema
      , LocalSecondaryIndex -> Projection
localProjection :: Projection
      }
    deriving (Int -> LocalSecondaryIndex -> String -> String
[LocalSecondaryIndex] -> String -> String
LocalSecondaryIndex -> String
(Int -> LocalSecondaryIndex -> String -> String)
-> (LocalSecondaryIndex -> String)
-> ([LocalSecondaryIndex] -> String -> String)
-> Show LocalSecondaryIndex
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> LocalSecondaryIndex -> String -> String
showsPrec :: Int -> LocalSecondaryIndex -> String -> String
$cshow :: LocalSecondaryIndex -> String
show :: LocalSecondaryIndex -> String
$cshowList :: [LocalSecondaryIndex] -> String -> String
showList :: [LocalSecondaryIndex] -> String -> String
Show, (forall x. LocalSecondaryIndex -> Rep LocalSecondaryIndex x)
-> (forall x. Rep LocalSecondaryIndex x -> LocalSecondaryIndex)
-> Generic LocalSecondaryIndex
forall x. Rep LocalSecondaryIndex x -> LocalSecondaryIndex
forall x. LocalSecondaryIndex -> Rep LocalSecondaryIndex x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LocalSecondaryIndex -> Rep LocalSecondaryIndex x
from :: forall x. LocalSecondaryIndex -> Rep LocalSecondaryIndex x
$cto :: forall x. Rep LocalSecondaryIndex x -> LocalSecondaryIndex
to :: forall x. Rep LocalSecondaryIndex x -> LocalSecondaryIndex
Generic)
instance A.ToJSON LocalSecondaryIndex where
    toJSON :: LocalSecondaryIndex -> Value
toJSON = Options -> LocalSecondaryIndex -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
A.genericToJSON (Options -> LocalSecondaryIndex -> Value)
-> Options -> LocalSecondaryIndex -> Value
forall a b. (a -> b) -> a -> b
$ Int -> Options
dropOpt Int
5
instance A.FromJSON LocalSecondaryIndex where
    parseJSON :: Value -> Parser LocalSecondaryIndex
parseJSON = Options -> Value -> Parser LocalSecondaryIndex
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
A.genericParseJSON (Options -> Value -> Parser LocalSecondaryIndex)
-> Options -> Value -> Parser LocalSecondaryIndex
forall a b. (a -> b) -> a -> b
$ Int -> Options
dropOpt Int
5

-- | This is returned by AWS to describe the local secondary index.
data LocalSecondaryIndexStatus
    = LocalSecondaryIndexStatus {
        LocalSecondaryIndexStatus -> Text
locStatusIndexName      :: T.Text
      , LocalSecondaryIndexStatus -> Integer
locStatusIndexSizeBytes :: Integer
      , LocalSecondaryIndexStatus -> Integer
locStatusItemCount      :: Integer
      , LocalSecondaryIndexStatus -> KeySchema
locStatusKeySchema      :: KeySchema
      , LocalSecondaryIndexStatus -> Projection
locStatusProjection     :: Projection
      }
    deriving (Int -> LocalSecondaryIndexStatus -> String -> String
[LocalSecondaryIndexStatus] -> String -> String
LocalSecondaryIndexStatus -> String
(Int -> LocalSecondaryIndexStatus -> String -> String)
-> (LocalSecondaryIndexStatus -> String)
-> ([LocalSecondaryIndexStatus] -> String -> String)
-> Show LocalSecondaryIndexStatus
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> LocalSecondaryIndexStatus -> String -> String
showsPrec :: Int -> LocalSecondaryIndexStatus -> String -> String
$cshow :: LocalSecondaryIndexStatus -> String
show :: LocalSecondaryIndexStatus -> String
$cshowList :: [LocalSecondaryIndexStatus] -> String -> String
showList :: [LocalSecondaryIndexStatus] -> String -> String
Show, (forall x.
 LocalSecondaryIndexStatus -> Rep LocalSecondaryIndexStatus x)
-> (forall x.
    Rep LocalSecondaryIndexStatus x -> LocalSecondaryIndexStatus)
-> Generic LocalSecondaryIndexStatus
forall x.
Rep LocalSecondaryIndexStatus x -> LocalSecondaryIndexStatus
forall x.
LocalSecondaryIndexStatus -> Rep LocalSecondaryIndexStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
LocalSecondaryIndexStatus -> Rep LocalSecondaryIndexStatus x
from :: forall x.
LocalSecondaryIndexStatus -> Rep LocalSecondaryIndexStatus x
$cto :: forall x.
Rep LocalSecondaryIndexStatus x -> LocalSecondaryIndexStatus
to :: forall x.
Rep LocalSecondaryIndexStatus x -> LocalSecondaryIndexStatus
Generic)
instance A.FromJSON LocalSecondaryIndexStatus where
    parseJSON :: Value -> Parser LocalSecondaryIndexStatus
parseJSON = Options -> Value -> Parser LocalSecondaryIndexStatus
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
A.genericParseJSON (Options -> Value -> Parser LocalSecondaryIndexStatus)
-> Options -> Value -> Parser LocalSecondaryIndexStatus
forall a b. (a -> b) -> a -> b
$ Int -> Options
dropOpt Int
9

-- | The target provisioned throughput you are requesting for the table or global secondary index.
data ProvisionedThroughput
    = ProvisionedThroughput {
        ProvisionedThroughput -> Int
readCapacityUnits  :: Int
      , ProvisionedThroughput -> Int
writeCapacityUnits :: Int
      }
    deriving (Int -> ProvisionedThroughput -> String -> String
[ProvisionedThroughput] -> String -> String
ProvisionedThroughput -> String
(Int -> ProvisionedThroughput -> String -> String)
-> (ProvisionedThroughput -> String)
-> ([ProvisionedThroughput] -> String -> String)
-> Show ProvisionedThroughput
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ProvisionedThroughput -> String -> String
showsPrec :: Int -> ProvisionedThroughput -> String -> String
$cshow :: ProvisionedThroughput -> String
show :: ProvisionedThroughput -> String
$cshowList :: [ProvisionedThroughput] -> String -> String
showList :: [ProvisionedThroughput] -> String -> String
Show, (forall x. ProvisionedThroughput -> Rep ProvisionedThroughput x)
-> (forall x. Rep ProvisionedThroughput x -> ProvisionedThroughput)
-> Generic ProvisionedThroughput
forall x. Rep ProvisionedThroughput x -> ProvisionedThroughput
forall x. ProvisionedThroughput -> Rep ProvisionedThroughput x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ProvisionedThroughput -> Rep ProvisionedThroughput x
from :: forall x. ProvisionedThroughput -> Rep ProvisionedThroughput x
$cto :: forall x. Rep ProvisionedThroughput x -> ProvisionedThroughput
to :: forall x. Rep ProvisionedThroughput x -> ProvisionedThroughput
Generic)
instance A.ToJSON ProvisionedThroughput where
    toJSON :: ProvisionedThroughput -> Value
toJSON = Options -> ProvisionedThroughput -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
A.genericToJSON Options
capitalizeOpt
instance A.FromJSON ProvisionedThroughput where
    parseJSON :: Value -> Parser ProvisionedThroughput
parseJSON = Options -> Value -> Parser ProvisionedThroughput
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
A.genericParseJSON Options
capitalizeOpt

-- | This is returned by AWS as the status of the throughput for a table or global secondary index.
data ProvisionedThroughputStatus
    = ProvisionedThroughputStatus {
        ProvisionedThroughputStatus -> UTCTime
statusLastDecreaseDateTime   :: UTCTime
      , ProvisionedThroughputStatus -> UTCTime
statusLastIncreaseDateTime   :: UTCTime
      , ProvisionedThroughputStatus -> Int
statusNumberOfDecreasesToday :: Int
      , ProvisionedThroughputStatus -> Int
statusReadCapacityUnits      :: Int
      , ProvisionedThroughputStatus -> Int
statusWriteCapacityUnits     :: Int
      }
    deriving (Int -> ProvisionedThroughputStatus -> String -> String
[ProvisionedThroughputStatus] -> String -> String
ProvisionedThroughputStatus -> String
(Int -> ProvisionedThroughputStatus -> String -> String)
-> (ProvisionedThroughputStatus -> String)
-> ([ProvisionedThroughputStatus] -> String -> String)
-> Show ProvisionedThroughputStatus
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ProvisionedThroughputStatus -> String -> String
showsPrec :: Int -> ProvisionedThroughputStatus -> String -> String
$cshow :: ProvisionedThroughputStatus -> String
show :: ProvisionedThroughputStatus -> String
$cshowList :: [ProvisionedThroughputStatus] -> String -> String
showList :: [ProvisionedThroughputStatus] -> String -> String
Show, (forall x.
 ProvisionedThroughputStatus -> Rep ProvisionedThroughputStatus x)
-> (forall x.
    Rep ProvisionedThroughputStatus x -> ProvisionedThroughputStatus)
-> Generic ProvisionedThroughputStatus
forall x.
Rep ProvisionedThroughputStatus x -> ProvisionedThroughputStatus
forall x.
ProvisionedThroughputStatus -> Rep ProvisionedThroughputStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
ProvisionedThroughputStatus -> Rep ProvisionedThroughputStatus x
from :: forall x.
ProvisionedThroughputStatus -> Rep ProvisionedThroughputStatus x
$cto :: forall x.
Rep ProvisionedThroughputStatus x -> ProvisionedThroughputStatus
to :: forall x.
Rep ProvisionedThroughputStatus x -> ProvisionedThroughputStatus
Generic)
instance A.FromJSON ProvisionedThroughputStatus where
    parseJSON :: Value -> Parser ProvisionedThroughputStatus
parseJSON = String
-> (Object -> Parser ProvisionedThroughputStatus)
-> Value
-> Parser ProvisionedThroughputStatus
forall a. String -> (Object -> Parser a) -> Value -> Parser a
A.withObject String
"Throughput status must be an object" ((Object -> Parser ProvisionedThroughputStatus)
 -> Value -> Parser ProvisionedThroughputStatus)
-> (Object -> Parser ProvisionedThroughputStatus)
-> Value
-> Parser ProvisionedThroughputStatus
forall a b. (a -> b) -> a -> b
$ \Object
o ->
        UTCTime
-> UTCTime -> Int -> Int -> Int -> ProvisionedThroughputStatus
ProvisionedThroughputStatus
            (UTCTime
 -> UTCTime -> Int -> Int -> Int -> ProvisionedThroughputStatus)
-> Parser UTCTime
-> Parser
     (UTCTime -> Int -> Int -> Int -> ProvisionedThroughputStatus)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Scientific -> UTCTime
convertToUTCTime (Scientific -> UTCTime) -> Parser Scientific -> Parser UTCTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe Scientific)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"LastDecreaseDateTime" Parser (Maybe Scientific) -> Scientific -> Parser Scientific
forall a. Parser (Maybe a) -> a -> Parser a
.!= Scientific
0)
            Parser
  (UTCTime -> Int -> Int -> Int -> ProvisionedThroughputStatus)
-> Parser UTCTime
-> Parser (Int -> Int -> Int -> ProvisionedThroughputStatus)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Scientific -> UTCTime
convertToUTCTime (Scientific -> UTCTime) -> Parser Scientific -> Parser UTCTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe Scientific)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"LastIncreaseDateTime" Parser (Maybe Scientific) -> Scientific -> Parser Scientific
forall a. Parser (Maybe a) -> a -> Parser a
.!= Scientific
0)
            Parser (Int -> Int -> Int -> ProvisionedThroughputStatus)
-> Parser Int -> Parser (Int -> Int -> ProvisionedThroughputStatus)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"NumberOfDecreasesToday" Parser (Maybe Int) -> Int -> Parser Int
forall a. Parser (Maybe a) -> a -> Parser a
.!= Int
0
            Parser (Int -> Int -> ProvisionedThroughputStatus)
-> Parser Int -> Parser (Int -> ProvisionedThroughputStatus)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"ReadCapacityUnits"
            Parser (Int -> ProvisionedThroughputStatus)
-> Parser Int -> Parser ProvisionedThroughputStatus
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"WriteCapacityUnits"

-- | Describes a global secondary index.
data GlobalSecondaryIndex
    = GlobalSecondaryIndex {
        GlobalSecondaryIndex -> Text
globalIndexName             :: T.Text
      , GlobalSecondaryIndex -> KeySchema
globalKeySchema             :: KeySchema
      , GlobalSecondaryIndex -> Projection
globalProjection            :: Projection
      , GlobalSecondaryIndex -> ProvisionedThroughput
globalProvisionedThroughput :: ProvisionedThroughput
      }
    deriving (Int -> GlobalSecondaryIndex -> String -> String
[GlobalSecondaryIndex] -> String -> String
GlobalSecondaryIndex -> String
(Int -> GlobalSecondaryIndex -> String -> String)
-> (GlobalSecondaryIndex -> String)
-> ([GlobalSecondaryIndex] -> String -> String)
-> Show GlobalSecondaryIndex
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> GlobalSecondaryIndex -> String -> String
showsPrec :: Int -> GlobalSecondaryIndex -> String -> String
$cshow :: GlobalSecondaryIndex -> String
show :: GlobalSecondaryIndex -> String
$cshowList :: [GlobalSecondaryIndex] -> String -> String
showList :: [GlobalSecondaryIndex] -> String -> String
Show, (forall x. GlobalSecondaryIndex -> Rep GlobalSecondaryIndex x)
-> (forall x. Rep GlobalSecondaryIndex x -> GlobalSecondaryIndex)
-> Generic GlobalSecondaryIndex
forall x. Rep GlobalSecondaryIndex x -> GlobalSecondaryIndex
forall x. GlobalSecondaryIndex -> Rep GlobalSecondaryIndex x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GlobalSecondaryIndex -> Rep GlobalSecondaryIndex x
from :: forall x. GlobalSecondaryIndex -> Rep GlobalSecondaryIndex x
$cto :: forall x. Rep GlobalSecondaryIndex x -> GlobalSecondaryIndex
to :: forall x. Rep GlobalSecondaryIndex x -> GlobalSecondaryIndex
Generic)
instance A.ToJSON GlobalSecondaryIndex where
    toJSON :: GlobalSecondaryIndex -> Value
toJSON = Options -> GlobalSecondaryIndex -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
A.genericToJSON (Options -> GlobalSecondaryIndex -> Value)
-> Options -> GlobalSecondaryIndex -> Value
forall a b. (a -> b) -> a -> b
$ Int -> Options
dropOpt Int
6
instance A.FromJSON GlobalSecondaryIndex where
    parseJSON :: Value -> Parser GlobalSecondaryIndex
parseJSON = Options -> Value -> Parser GlobalSecondaryIndex
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
A.genericParseJSON (Options -> Value -> Parser GlobalSecondaryIndex)
-> Options -> Value -> Parser GlobalSecondaryIndex
forall a b. (a -> b) -> a -> b
$ Int -> Options
dropOpt Int
6

-- | This is returned by AWS to describe the status of a global secondary index.
data GlobalSecondaryIndexStatus
    = GlobalSecondaryIndexStatus {
        GlobalSecondaryIndexStatus -> Text
gStatusIndexName             :: T.Text
      , GlobalSecondaryIndexStatus -> Integer
gStatusIndexSizeBytes        :: Integer
      , GlobalSecondaryIndexStatus -> Text
gStatusIndexStatus           :: T.Text
      , GlobalSecondaryIndexStatus -> Integer
gStatusItemCount             :: Integer
      , GlobalSecondaryIndexStatus -> KeySchema
gStatusKeySchema             :: KeySchema
      , GlobalSecondaryIndexStatus -> Projection
gStatusProjection            :: Projection
      , GlobalSecondaryIndexStatus -> ProvisionedThroughputStatus
gStatusProvisionedThroughput :: ProvisionedThroughputStatus
      }
    deriving (Int -> GlobalSecondaryIndexStatus -> String -> String
[GlobalSecondaryIndexStatus] -> String -> String
GlobalSecondaryIndexStatus -> String
(Int -> GlobalSecondaryIndexStatus -> String -> String)
-> (GlobalSecondaryIndexStatus -> String)
-> ([GlobalSecondaryIndexStatus] -> String -> String)
-> Show GlobalSecondaryIndexStatus
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> GlobalSecondaryIndexStatus -> String -> String
showsPrec :: Int -> GlobalSecondaryIndexStatus -> String -> String
$cshow :: GlobalSecondaryIndexStatus -> String
show :: GlobalSecondaryIndexStatus -> String
$cshowList :: [GlobalSecondaryIndexStatus] -> String -> String
showList :: [GlobalSecondaryIndexStatus] -> String -> String
Show, (forall x.
 GlobalSecondaryIndexStatus -> Rep GlobalSecondaryIndexStatus x)
-> (forall x.
    Rep GlobalSecondaryIndexStatus x -> GlobalSecondaryIndexStatus)
-> Generic GlobalSecondaryIndexStatus
forall x.
Rep GlobalSecondaryIndexStatus x -> GlobalSecondaryIndexStatus
forall x.
GlobalSecondaryIndexStatus -> Rep GlobalSecondaryIndexStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
GlobalSecondaryIndexStatus -> Rep GlobalSecondaryIndexStatus x
from :: forall x.
GlobalSecondaryIndexStatus -> Rep GlobalSecondaryIndexStatus x
$cto :: forall x.
Rep GlobalSecondaryIndexStatus x -> GlobalSecondaryIndexStatus
to :: forall x.
Rep GlobalSecondaryIndexStatus x -> GlobalSecondaryIndexStatus
Generic)
instance A.FromJSON GlobalSecondaryIndexStatus where
    parseJSON :: Value -> Parser GlobalSecondaryIndexStatus
parseJSON = Options -> Value -> Parser GlobalSecondaryIndexStatus
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
A.genericParseJSON (Options -> Value -> Parser GlobalSecondaryIndexStatus)
-> Options -> Value -> Parser GlobalSecondaryIndexStatus
forall a b. (a -> b) -> a -> b
$ Int -> Options
dropOpt Int
7

-- | This is used to request a change in the provisioned throughput of
-- a global secondary index as part of an 'UpdateTable' operation.
data GlobalSecondaryIndexUpdate
    = GlobalSecondaryIndexUpdate {
        GlobalSecondaryIndexUpdate -> Text
gUpdateIndexName             :: T.Text
      , GlobalSecondaryIndexUpdate -> ProvisionedThroughput
gUpdateProvisionedThroughput :: ProvisionedThroughput
      }
    deriving (Int -> GlobalSecondaryIndexUpdate -> String -> String
[GlobalSecondaryIndexUpdate] -> String -> String
GlobalSecondaryIndexUpdate -> String
(Int -> GlobalSecondaryIndexUpdate -> String -> String)
-> (GlobalSecondaryIndexUpdate -> String)
-> ([GlobalSecondaryIndexUpdate] -> String -> String)
-> Show GlobalSecondaryIndexUpdate
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> GlobalSecondaryIndexUpdate -> String -> String
showsPrec :: Int -> GlobalSecondaryIndexUpdate -> String -> String
$cshow :: GlobalSecondaryIndexUpdate -> String
show :: GlobalSecondaryIndexUpdate -> String
$cshowList :: [GlobalSecondaryIndexUpdate] -> String -> String
showList :: [GlobalSecondaryIndexUpdate] -> String -> String
Show, (forall x.
 GlobalSecondaryIndexUpdate -> Rep GlobalSecondaryIndexUpdate x)
-> (forall x.
    Rep GlobalSecondaryIndexUpdate x -> GlobalSecondaryIndexUpdate)
-> Generic GlobalSecondaryIndexUpdate
forall x.
Rep GlobalSecondaryIndexUpdate x -> GlobalSecondaryIndexUpdate
forall x.
GlobalSecondaryIndexUpdate -> Rep GlobalSecondaryIndexUpdate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
GlobalSecondaryIndexUpdate -> Rep GlobalSecondaryIndexUpdate x
from :: forall x.
GlobalSecondaryIndexUpdate -> Rep GlobalSecondaryIndexUpdate x
$cto :: forall x.
Rep GlobalSecondaryIndexUpdate x -> GlobalSecondaryIndexUpdate
to :: forall x.
Rep GlobalSecondaryIndexUpdate x -> GlobalSecondaryIndexUpdate
Generic)
instance A.ToJSON GlobalSecondaryIndexUpdate where
    toJSON :: GlobalSecondaryIndexUpdate -> Value
toJSON GlobalSecondaryIndexUpdate
gi = [Pair] -> Value
A.object [Key
"Update" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Options -> GlobalSecondaryIndexUpdate -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
A.genericToJSON (Int -> Options
dropOpt Int
7) GlobalSecondaryIndexUpdate
gi]

-- | This describes the table and is the return value from AWS for all
-- the table-related commands.
data TableDescription
    = TableDescription {
        TableDescription -> Text
rTableName              :: T.Text
      , TableDescription -> Integer
rTableSizeBytes         :: Integer
      , TableDescription -> Text
rTableStatus            :: T.Text -- ^ one of CREATING, UPDATING, DELETING, ACTIVE
      , TableDescription -> Maybe UTCTime
rCreationDateTime       :: Maybe UTCTime
      , TableDescription -> Integer
rItemCount              :: Integer
      , TableDescription -> [AttributeDefinition]
rAttributeDefinitions   :: [AttributeDefinition]
      , TableDescription -> Maybe KeySchema
rKeySchema              :: Maybe KeySchema
      , TableDescription -> ProvisionedThroughputStatus
rProvisionedThroughput  :: ProvisionedThroughputStatus
      , TableDescription -> [LocalSecondaryIndexStatus]
rLocalSecondaryIndexes  :: [LocalSecondaryIndexStatus]
      , TableDescription -> [GlobalSecondaryIndexStatus]
rGlobalSecondaryIndexes :: [GlobalSecondaryIndexStatus]
      }
    deriving (Int -> TableDescription -> String -> String
[TableDescription] -> String -> String
TableDescription -> String
(Int -> TableDescription -> String -> String)
-> (TableDescription -> String)
-> ([TableDescription] -> String -> String)
-> Show TableDescription
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> TableDescription -> String -> String
showsPrec :: Int -> TableDescription -> String -> String
$cshow :: TableDescription -> String
show :: TableDescription -> String
$cshowList :: [TableDescription] -> String -> String
showList :: [TableDescription] -> String -> String
Show, (forall x. TableDescription -> Rep TableDescription x)
-> (forall x. Rep TableDescription x -> TableDescription)
-> Generic TableDescription
forall x. Rep TableDescription x -> TableDescription
forall x. TableDescription -> Rep TableDescription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TableDescription -> Rep TableDescription x
from :: forall x. TableDescription -> Rep TableDescription x
$cto :: forall x. Rep TableDescription x -> TableDescription
to :: forall x. Rep TableDescription x -> TableDescription
Generic)

instance A.FromJSON TableDescription where
    parseJSON :: Value -> Parser TableDescription
parseJSON = String
-> (Object -> Parser TableDescription)
-> Value
-> Parser TableDescription
forall a. String -> (Object -> Parser a) -> Value -> Parser a
A.withObject String
"Table must be an object" ((Object -> Parser TableDescription)
 -> Value -> Parser TableDescription)
-> (Object -> Parser TableDescription)
-> Value
-> Parser TableDescription
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
        Object
t <- case (Key -> Object -> Maybe Value
forall v. Key -> KeyMap v -> Maybe v
KM.lookup Key
"Table" Object
o, Key -> Object -> Maybe Value
forall v. Key -> KeyMap v -> Maybe v
KM.lookup Key
"TableDescription" Object
o) of
                (Just (A.Object Object
t), Maybe Value
_) -> Object -> Parser Object
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return Object
t
                (Maybe Value
_, Just (A.Object Object
t)) -> Object -> Parser Object
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return Object
t
                (Maybe Value, Maybe Value)
_ -> String -> Parser Object
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Table description must have key 'Table' or 'TableDescription'"
        Text
-> Integer
-> Text
-> Maybe UTCTime
-> Integer
-> [AttributeDefinition]
-> Maybe KeySchema
-> ProvisionedThroughputStatus
-> [LocalSecondaryIndexStatus]
-> [GlobalSecondaryIndexStatus]
-> TableDescription
TableDescription (Text
 -> Integer
 -> Text
 -> Maybe UTCTime
 -> Integer
 -> [AttributeDefinition]
 -> Maybe KeySchema
 -> ProvisionedThroughputStatus
 -> [LocalSecondaryIndexStatus]
 -> [GlobalSecondaryIndexStatus]
 -> TableDescription)
-> Parser Text
-> Parser
     (Integer
      -> Text
      -> Maybe UTCTime
      -> Integer
      -> [AttributeDefinition]
      -> Maybe KeySchema
      -> ProvisionedThroughputStatus
      -> [LocalSecondaryIndexStatus]
      -> [GlobalSecondaryIndexStatus]
      -> TableDescription)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
t Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"TableName"
                         Parser
  (Integer
   -> Text
   -> Maybe UTCTime
   -> Integer
   -> [AttributeDefinition]
   -> Maybe KeySchema
   -> ProvisionedThroughputStatus
   -> [LocalSecondaryIndexStatus]
   -> [GlobalSecondaryIndexStatus]
   -> TableDescription)
-> Parser Integer
-> Parser
     (Text
      -> Maybe UTCTime
      -> Integer
      -> [AttributeDefinition]
      -> Maybe KeySchema
      -> ProvisionedThroughputStatus
      -> [LocalSecondaryIndexStatus]
      -> [GlobalSecondaryIndexStatus]
      -> TableDescription)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
t Object -> Key -> Parser Integer
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"TableSizeBytes"
                         Parser
  (Text
   -> Maybe UTCTime
   -> Integer
   -> [AttributeDefinition]
   -> Maybe KeySchema
   -> ProvisionedThroughputStatus
   -> [LocalSecondaryIndexStatus]
   -> [GlobalSecondaryIndexStatus]
   -> TableDescription)
-> Parser Text
-> Parser
     (Maybe UTCTime
      -> Integer
      -> [AttributeDefinition]
      -> Maybe KeySchema
      -> ProvisionedThroughputStatus
      -> [LocalSecondaryIndexStatus]
      -> [GlobalSecondaryIndexStatus]
      -> TableDescription)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
t Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"TableStatus"
                         Parser
  (Maybe UTCTime
   -> Integer
   -> [AttributeDefinition]
   -> Maybe KeySchema
   -> ProvisionedThroughputStatus
   -> [LocalSecondaryIndexStatus]
   -> [GlobalSecondaryIndexStatus]
   -> TableDescription)
-> Parser (Maybe UTCTime)
-> Parser
     (Integer
      -> [AttributeDefinition]
      -> Maybe KeySchema
      -> ProvisionedThroughputStatus
      -> [LocalSecondaryIndexStatus]
      -> [GlobalSecondaryIndexStatus]
      -> TableDescription)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Scientific -> UTCTime) -> Maybe Scientific -> Maybe UTCTime
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Scientific -> UTCTime
convertToUTCTime (Maybe Scientific -> Maybe UTCTime)
-> Parser (Maybe Scientific) -> Parser (Maybe UTCTime)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
t Object -> Key -> Parser (Maybe Scientific)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"CreationDateTime")
                         Parser
  (Integer
   -> [AttributeDefinition]
   -> Maybe KeySchema
   -> ProvisionedThroughputStatus
   -> [LocalSecondaryIndexStatus]
   -> [GlobalSecondaryIndexStatus]
   -> TableDescription)
-> Parser Integer
-> Parser
     ([AttributeDefinition]
      -> Maybe KeySchema
      -> ProvisionedThroughputStatus
      -> [LocalSecondaryIndexStatus]
      -> [GlobalSecondaryIndexStatus]
      -> TableDescription)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
t Object -> Key -> Parser Integer
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"ItemCount"
                         Parser
  ([AttributeDefinition]
   -> Maybe KeySchema
   -> ProvisionedThroughputStatus
   -> [LocalSecondaryIndexStatus]
   -> [GlobalSecondaryIndexStatus]
   -> TableDescription)
-> Parser [AttributeDefinition]
-> Parser
     (Maybe KeySchema
      -> ProvisionedThroughputStatus
      -> [LocalSecondaryIndexStatus]
      -> [GlobalSecondaryIndexStatus]
      -> TableDescription)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
t Object -> Key -> Parser (Maybe [AttributeDefinition])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"AttributeDefinitions" Parser (Maybe [AttributeDefinition])
-> [AttributeDefinition] -> Parser [AttributeDefinition]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []
                         Parser
  (Maybe KeySchema
   -> ProvisionedThroughputStatus
   -> [LocalSecondaryIndexStatus]
   -> [GlobalSecondaryIndexStatus]
   -> TableDescription)
-> Parser (Maybe KeySchema)
-> Parser
     (ProvisionedThroughputStatus
      -> [LocalSecondaryIndexStatus]
      -> [GlobalSecondaryIndexStatus]
      -> TableDescription)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
t Object -> Key -> Parser (Maybe KeySchema)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"KeySchema"
                         Parser
  (ProvisionedThroughputStatus
   -> [LocalSecondaryIndexStatus]
   -> [GlobalSecondaryIndexStatus]
   -> TableDescription)
-> Parser ProvisionedThroughputStatus
-> Parser
     ([LocalSecondaryIndexStatus]
      -> [GlobalSecondaryIndexStatus] -> TableDescription)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
t Object -> Key -> Parser ProvisionedThroughputStatus
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"ProvisionedThroughput"
                         Parser
  ([LocalSecondaryIndexStatus]
   -> [GlobalSecondaryIndexStatus] -> TableDescription)
-> Parser [LocalSecondaryIndexStatus]
-> Parser ([GlobalSecondaryIndexStatus] -> TableDescription)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
t Object -> Key -> Parser (Maybe [LocalSecondaryIndexStatus])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"LocalSecondaryIndexes" Parser (Maybe [LocalSecondaryIndexStatus])
-> [LocalSecondaryIndexStatus]
-> Parser [LocalSecondaryIndexStatus]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []
                         Parser ([GlobalSecondaryIndexStatus] -> TableDescription)
-> Parser [GlobalSecondaryIndexStatus] -> Parser TableDescription
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
t Object -> Key -> Parser (Maybe [GlobalSecondaryIndexStatus])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"GlobalSecondaryIndexes" Parser (Maybe [GlobalSecondaryIndexStatus])
-> [GlobalSecondaryIndexStatus]
-> Parser [GlobalSecondaryIndexStatus]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []

{- Can't derive these instances onto the return values
instance ResponseConsumer r TableDescription where
    type ResponseMetadata TableDescription = DyMetadata
    responseConsumer _ _ _ = ddbResponseConsumer
instance AsMemoryResponse TableDescription where
    type MemoryResponse TableDescription = TableDescription
    loadToMemory = return
-}

-------------------------------------------------------------------------------
--- Commands
-------------------------------------------------------------------------------

data CreateTable = CreateTable {
      CreateTable -> Text
createTableName              :: T.Text
    , CreateTable -> [AttributeDefinition]
createAttributeDefinitions   :: [AttributeDefinition]
    -- ^ only attributes appearing in a key must be listed here
    , CreateTable -> KeySchema
createKeySchema              :: KeySchema
    , CreateTable -> ProvisionedThroughput
createProvisionedThroughput  :: ProvisionedThroughput
    , CreateTable -> [LocalSecondaryIndex]
createLocalSecondaryIndexes  :: [LocalSecondaryIndex]
    -- ^ at most 5 local secondary indices are allowed
    , CreateTable -> [GlobalSecondaryIndex]
createGlobalSecondaryIndexes :: [GlobalSecondaryIndex]
    } deriving (Int -> CreateTable -> String -> String
[CreateTable] -> String -> String
CreateTable -> String
(Int -> CreateTable -> String -> String)
-> (CreateTable -> String)
-> ([CreateTable] -> String -> String)
-> Show CreateTable
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> CreateTable -> String -> String
showsPrec :: Int -> CreateTable -> String -> String
$cshow :: CreateTable -> String
show :: CreateTable -> String
$cshowList :: [CreateTable] -> String -> String
showList :: [CreateTable] -> String -> String
Show, (forall x. CreateTable -> Rep CreateTable x)
-> (forall x. Rep CreateTable x -> CreateTable)
-> Generic CreateTable
forall x. Rep CreateTable x -> CreateTable
forall x. CreateTable -> Rep CreateTable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CreateTable -> Rep CreateTable x
from :: forall x. CreateTable -> Rep CreateTable x
$cto :: forall x. Rep CreateTable x -> CreateTable
to :: forall x. Rep CreateTable x -> CreateTable
Generic)

createTable :: T.Text -- ^ Table name
            -> [AttributeDefinition]
            -> KeySchema
            -> ProvisionedThroughput
            -> CreateTable
createTable :: Text
-> [AttributeDefinition]
-> KeySchema
-> ProvisionedThroughput
-> CreateTable
createTable Text
tn [AttributeDefinition]
ad KeySchema
ks ProvisionedThroughput
p = Text
-> [AttributeDefinition]
-> KeySchema
-> ProvisionedThroughput
-> [LocalSecondaryIndex]
-> [GlobalSecondaryIndex]
-> CreateTable
CreateTable Text
tn [AttributeDefinition]
ad KeySchema
ks ProvisionedThroughput
p [] []

instance A.ToJSON CreateTable where
    toJSON :: CreateTable -> Value
toJSON CreateTable
ct = [Pair] -> Value
A.object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [Pair]
m [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair]
lindex [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair]
gindex
        where
            m :: [Pair]
m = [ Key
"TableName" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= CreateTable -> Text
createTableName CreateTable
ct
                , Key
"AttributeDefinitions" Key -> [AttributeDefinition] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= CreateTable -> [AttributeDefinition]
createAttributeDefinitions CreateTable
ct
                , Key
"KeySchema" Key -> KeySchema -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= CreateTable -> KeySchema
createKeySchema CreateTable
ct
                , Key
"ProvisionedThroughput" Key -> ProvisionedThroughput -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= CreateTable -> ProvisionedThroughput
createProvisionedThroughput CreateTable
ct
                ]
            -- AWS will error with 500 if (LocalSecondaryIndexes : []) is present in the JSON
            lindex :: [Pair]
lindex = if [LocalSecondaryIndex] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (CreateTable -> [LocalSecondaryIndex]
createLocalSecondaryIndexes CreateTable
ct)
                        then []
                        else [ Key
"LocalSecondaryIndexes" Key -> [LocalSecondaryIndex] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= CreateTable -> [LocalSecondaryIndex]
createLocalSecondaryIndexes CreateTable
ct ]
            gindex :: [Pair]
gindex = if [GlobalSecondaryIndex] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (CreateTable -> [GlobalSecondaryIndex]
createGlobalSecondaryIndexes CreateTable
ct)
                        then []
                        else [ Key
"GlobalSecondaryIndexes" Key -> [GlobalSecondaryIndex] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= CreateTable -> [GlobalSecondaryIndex]
createGlobalSecondaryIndexes CreateTable
ct ]

--instance A.ToJSON CreateTable where
--    toJSON = A.genericToJSON $ dropOpt 6


-- | ServiceConfiguration: 'DdbConfiguration'
instance SignQuery CreateTable where
    type ServiceConfiguration CreateTable = DdbConfiguration
    signQuery :: forall queryType.
CreateTable
-> ServiceConfiguration CreateTable queryType
-> SignatureData
-> SignedQuery
signQuery = ByteString
-> CreateTable
-> DdbConfiguration queryType
-> SignatureData
-> SignedQuery
forall a qt.
ToJSON a =>
ByteString
-> a -> DdbConfiguration qt -> SignatureData -> SignedQuery
ddbSignQuery ByteString
"CreateTable"

newtype CreateTableResult = CreateTableResult { CreateTableResult -> TableDescription
ctStatus :: TableDescription }
    deriving (Int -> CreateTableResult -> String -> String
[CreateTableResult] -> String -> String
CreateTableResult -> String
(Int -> CreateTableResult -> String -> String)
-> (CreateTableResult -> String)
-> ([CreateTableResult] -> String -> String)
-> Show CreateTableResult
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> CreateTableResult -> String -> String
showsPrec :: Int -> CreateTableResult -> String -> String
$cshow :: CreateTableResult -> String
show :: CreateTableResult -> String
$cshowList :: [CreateTableResult] -> String -> String
showList :: [CreateTableResult] -> String -> String
Show, Maybe CreateTableResult
Value -> Parser [CreateTableResult]
Value -> Parser CreateTableResult
(Value -> Parser CreateTableResult)
-> (Value -> Parser [CreateTableResult])
-> Maybe CreateTableResult
-> FromJSON CreateTableResult
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser CreateTableResult
parseJSON :: Value -> Parser CreateTableResult
$cparseJSONList :: Value -> Parser [CreateTableResult]
parseJSONList :: Value -> Parser [CreateTableResult]
$comittedField :: Maybe CreateTableResult
omittedField :: Maybe CreateTableResult
A.FromJSON)
-- ResponseConsumer and AsMemoryResponse can't be derived
instance ResponseConsumer r CreateTableResult where
    type ResponseMetadata CreateTableResult = DdbResponse
    responseConsumer :: Request
-> r
-> IORef (ResponseMetadata CreateTableResult)
-> HTTPResponseConsumer CreateTableResult
responseConsumer Request
_ r
_ = IORef (ResponseMetadata CreateTableResult)
-> HTTPResponseConsumer CreateTableResult
IORef DdbResponse -> HTTPResponseConsumer CreateTableResult
forall a. FromJSON a => IORef DdbResponse -> HTTPResponseConsumer a
ddbResponseConsumer
instance AsMemoryResponse CreateTableResult where
    type MemoryResponse CreateTableResult = TableDescription
    loadToMemory :: CreateTableResult
-> ResourceT IO (MemoryResponse CreateTableResult)
loadToMemory = TableDescription -> ResourceT IO TableDescription
forall a. a -> ResourceT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (TableDescription -> ResourceT IO TableDescription)
-> (CreateTableResult -> TableDescription)
-> CreateTableResult
-> ResourceT IO TableDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CreateTableResult -> TableDescription
ctStatus

instance Transaction CreateTable CreateTableResult

data DescribeTable
    = DescribeTable {
        DescribeTable -> Text
dTableName :: T.Text
      }
    deriving (Int -> DescribeTable -> String -> String
[DescribeTable] -> String -> String
DescribeTable -> String
(Int -> DescribeTable -> String -> String)
-> (DescribeTable -> String)
-> ([DescribeTable] -> String -> String)
-> Show DescribeTable
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> DescribeTable -> String -> String
showsPrec :: Int -> DescribeTable -> String -> String
$cshow :: DescribeTable -> String
show :: DescribeTable -> String
$cshowList :: [DescribeTable] -> String -> String
showList :: [DescribeTable] -> String -> String
Show, (forall x. DescribeTable -> Rep DescribeTable x)
-> (forall x. Rep DescribeTable x -> DescribeTable)
-> Generic DescribeTable
forall x. Rep DescribeTable x -> DescribeTable
forall x. DescribeTable -> Rep DescribeTable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DescribeTable -> Rep DescribeTable x
from :: forall x. DescribeTable -> Rep DescribeTable x
$cto :: forall x. Rep DescribeTable x -> DescribeTable
to :: forall x. Rep DescribeTable x -> DescribeTable
Generic)
instance A.ToJSON DescribeTable where
    toJSON :: DescribeTable -> Value
toJSON = Options -> DescribeTable -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
A.genericToJSON (Options -> DescribeTable -> Value)
-> Options -> DescribeTable -> Value
forall a b. (a -> b) -> a -> b
$ Int -> Options
dropOpt Int
1

-- | ServiceConfiguration: 'DdbConfiguration'
instance SignQuery DescribeTable where
    type ServiceConfiguration DescribeTable = DdbConfiguration
    signQuery :: forall queryType.
DescribeTable
-> ServiceConfiguration DescribeTable queryType
-> SignatureData
-> SignedQuery
signQuery = ByteString
-> DescribeTable
-> DdbConfiguration queryType
-> SignatureData
-> SignedQuery
forall a qt.
ToJSON a =>
ByteString
-> a -> DdbConfiguration qt -> SignatureData -> SignedQuery
ddbSignQuery ByteString
"DescribeTable"

newtype DescribeTableResult = DescribeTableResult { DescribeTableResult -> TableDescription
dtStatus :: TableDescription }
    deriving (Int -> DescribeTableResult -> String -> String
[DescribeTableResult] -> String -> String
DescribeTableResult -> String
(Int -> DescribeTableResult -> String -> String)
-> (DescribeTableResult -> String)
-> ([DescribeTableResult] -> String -> String)
-> Show DescribeTableResult
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> DescribeTableResult -> String -> String
showsPrec :: Int -> DescribeTableResult -> String -> String
$cshow :: DescribeTableResult -> String
show :: DescribeTableResult -> String
$cshowList :: [DescribeTableResult] -> String -> String
showList :: [DescribeTableResult] -> String -> String
Show, Maybe DescribeTableResult
Value -> Parser [DescribeTableResult]
Value -> Parser DescribeTableResult
(Value -> Parser DescribeTableResult)
-> (Value -> Parser [DescribeTableResult])
-> Maybe DescribeTableResult
-> FromJSON DescribeTableResult
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser DescribeTableResult
parseJSON :: Value -> Parser DescribeTableResult
$cparseJSONList :: Value -> Parser [DescribeTableResult]
parseJSONList :: Value -> Parser [DescribeTableResult]
$comittedField :: Maybe DescribeTableResult
omittedField :: Maybe DescribeTableResult
A.FromJSON)
-- ResponseConsumer can't be derived
instance ResponseConsumer r DescribeTableResult where
    type ResponseMetadata DescribeTableResult = DdbResponse
    responseConsumer :: Request
-> r
-> IORef (ResponseMetadata DescribeTableResult)
-> HTTPResponseConsumer DescribeTableResult
responseConsumer Request
_ r
_ = IORef (ResponseMetadata DescribeTableResult)
-> HTTPResponseConsumer DescribeTableResult
IORef DdbResponse -> HTTPResponseConsumer DescribeTableResult
forall a. FromJSON a => IORef DdbResponse -> HTTPResponseConsumer a
ddbResponseConsumer
instance AsMemoryResponse DescribeTableResult where
    type MemoryResponse DescribeTableResult = TableDescription
    loadToMemory :: DescribeTableResult
-> ResourceT IO (MemoryResponse DescribeTableResult)
loadToMemory = TableDescription -> ResourceT IO TableDescription
forall a. a -> ResourceT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (TableDescription -> ResourceT IO TableDescription)
-> (DescribeTableResult -> TableDescription)
-> DescribeTableResult
-> ResourceT IO TableDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DescribeTableResult -> TableDescription
dtStatus

instance Transaction DescribeTable DescribeTableResult

data UpdateTable
    = UpdateTable {
        UpdateTable -> Text
updateTableName                   :: T.Text
      , UpdateTable -> ProvisionedThroughput
updateProvisionedThroughput       :: ProvisionedThroughput
      , UpdateTable -> [GlobalSecondaryIndexUpdate]
updateGlobalSecondaryIndexUpdates :: [GlobalSecondaryIndexUpdate]
      }
    deriving (Int -> UpdateTable -> String -> String
[UpdateTable] -> String -> String
UpdateTable -> String
(Int -> UpdateTable -> String -> String)
-> (UpdateTable -> String)
-> ([UpdateTable] -> String -> String)
-> Show UpdateTable
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> UpdateTable -> String -> String
showsPrec :: Int -> UpdateTable -> String -> String
$cshow :: UpdateTable -> String
show :: UpdateTable -> String
$cshowList :: [UpdateTable] -> String -> String
showList :: [UpdateTable] -> String -> String
Show, (forall x. UpdateTable -> Rep UpdateTable x)
-> (forall x. Rep UpdateTable x -> UpdateTable)
-> Generic UpdateTable
forall x. Rep UpdateTable x -> UpdateTable
forall x. UpdateTable -> Rep UpdateTable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. UpdateTable -> Rep UpdateTable x
from :: forall x. UpdateTable -> Rep UpdateTable x
$cto :: forall x. Rep UpdateTable x -> UpdateTable
to :: forall x. Rep UpdateTable x -> UpdateTable
Generic)
instance A.ToJSON UpdateTable where
    toJSON :: UpdateTable -> Value
toJSON UpdateTable
a = [Pair] -> Value
A.object
        ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ Key
"TableName" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= UpdateTable -> Text
updateTableName UpdateTable
a
        Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Key
"ProvisionedThroughput" Key -> ProvisionedThroughput -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= UpdateTable -> ProvisionedThroughput
updateProvisionedThroughput UpdateTable
a
        Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: case UpdateTable -> [GlobalSecondaryIndexUpdate]
updateGlobalSecondaryIndexUpdates UpdateTable
a of
            [] -> []
            [GlobalSecondaryIndexUpdate]
l -> [ Key
"GlobalSecondaryIndexUpdates" Key -> [GlobalSecondaryIndexUpdate] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [GlobalSecondaryIndexUpdate]
l ]

-- | ServiceConfiguration: 'DdbConfiguration'
instance SignQuery UpdateTable where
    type ServiceConfiguration UpdateTable = DdbConfiguration
    signQuery :: forall queryType.
UpdateTable
-> ServiceConfiguration UpdateTable queryType
-> SignatureData
-> SignedQuery
signQuery = ByteString
-> UpdateTable
-> DdbConfiguration queryType
-> SignatureData
-> SignedQuery
forall a qt.
ToJSON a =>
ByteString
-> a -> DdbConfiguration qt -> SignatureData -> SignedQuery
ddbSignQuery ByteString
"UpdateTable"

newtype UpdateTableResult = UpdateTableResult { UpdateTableResult -> TableDescription
uStatus :: TableDescription }
    deriving (Int -> UpdateTableResult -> String -> String
[UpdateTableResult] -> String -> String
UpdateTableResult -> String
(Int -> UpdateTableResult -> String -> String)
-> (UpdateTableResult -> String)
-> ([UpdateTableResult] -> String -> String)
-> Show UpdateTableResult
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> UpdateTableResult -> String -> String
showsPrec :: Int -> UpdateTableResult -> String -> String
$cshow :: UpdateTableResult -> String
show :: UpdateTableResult -> String
$cshowList :: [UpdateTableResult] -> String -> String
showList :: [UpdateTableResult] -> String -> String
Show, Maybe UpdateTableResult
Value -> Parser [UpdateTableResult]
Value -> Parser UpdateTableResult
(Value -> Parser UpdateTableResult)
-> (Value -> Parser [UpdateTableResult])
-> Maybe UpdateTableResult
-> FromJSON UpdateTableResult
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser UpdateTableResult
parseJSON :: Value -> Parser UpdateTableResult
$cparseJSONList :: Value -> Parser [UpdateTableResult]
parseJSONList :: Value -> Parser [UpdateTableResult]
$comittedField :: Maybe UpdateTableResult
omittedField :: Maybe UpdateTableResult
A.FromJSON)
-- ResponseConsumer can't be derived
instance ResponseConsumer r UpdateTableResult where
    type ResponseMetadata UpdateTableResult = DdbResponse
    responseConsumer :: Request
-> r
-> IORef (ResponseMetadata UpdateTableResult)
-> HTTPResponseConsumer UpdateTableResult
responseConsumer Request
_ r
_ = IORef (ResponseMetadata UpdateTableResult)
-> HTTPResponseConsumer UpdateTableResult
IORef DdbResponse -> HTTPResponseConsumer UpdateTableResult
forall a. FromJSON a => IORef DdbResponse -> HTTPResponseConsumer a
ddbResponseConsumer
instance AsMemoryResponse UpdateTableResult where
    type MemoryResponse UpdateTableResult = TableDescription
    loadToMemory :: UpdateTableResult
-> ResourceT IO (MemoryResponse UpdateTableResult)
loadToMemory = TableDescription -> ResourceT IO TableDescription
forall a. a -> ResourceT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (TableDescription -> ResourceT IO TableDescription)
-> (UpdateTableResult -> TableDescription)
-> UpdateTableResult
-> ResourceT IO TableDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UpdateTableResult -> TableDescription
uStatus

instance Transaction UpdateTable UpdateTableResult

data DeleteTable
    = DeleteTable {
        DeleteTable -> Text
deleteTableName :: T.Text
      }
    deriving (Int -> DeleteTable -> String -> String
[DeleteTable] -> String -> String
DeleteTable -> String
(Int -> DeleteTable -> String -> String)
-> (DeleteTable -> String)
-> ([DeleteTable] -> String -> String)
-> Show DeleteTable
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> DeleteTable -> String -> String
showsPrec :: Int -> DeleteTable -> String -> String
$cshow :: DeleteTable -> String
show :: DeleteTable -> String
$cshowList :: [DeleteTable] -> String -> String
showList :: [DeleteTable] -> String -> String
Show, (forall x. DeleteTable -> Rep DeleteTable x)
-> (forall x. Rep DeleteTable x -> DeleteTable)
-> Generic DeleteTable
forall x. Rep DeleteTable x -> DeleteTable
forall x. DeleteTable -> Rep DeleteTable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DeleteTable -> Rep DeleteTable x
from :: forall x. DeleteTable -> Rep DeleteTable x
$cto :: forall x. Rep DeleteTable x -> DeleteTable
to :: forall x. Rep DeleteTable x -> DeleteTable
Generic)
instance A.ToJSON DeleteTable where
    toJSON :: DeleteTable -> Value
toJSON = Options -> DeleteTable -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
A.genericToJSON (Options -> DeleteTable -> Value)
-> Options -> DeleteTable -> Value
forall a b. (a -> b) -> a -> b
$ Int -> Options
dropOpt Int
6

-- | ServiceConfiguration: 'DdbConfiguration'
instance SignQuery DeleteTable where
    type ServiceConfiguration DeleteTable = DdbConfiguration
    signQuery :: forall queryType.
DeleteTable
-> ServiceConfiguration DeleteTable queryType
-> SignatureData
-> SignedQuery
signQuery = ByteString
-> DeleteTable
-> DdbConfiguration queryType
-> SignatureData
-> SignedQuery
forall a qt.
ToJSON a =>
ByteString
-> a -> DdbConfiguration qt -> SignatureData -> SignedQuery
ddbSignQuery ByteString
"DeleteTable"

newtype DeleteTableResult = DeleteTableResult { DeleteTableResult -> TableDescription
dStatus :: TableDescription }
    deriving (Int -> DeleteTableResult -> String -> String
[DeleteTableResult] -> String -> String
DeleteTableResult -> String
(Int -> DeleteTableResult -> String -> String)
-> (DeleteTableResult -> String)
-> ([DeleteTableResult] -> String -> String)
-> Show DeleteTableResult
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> DeleteTableResult -> String -> String
showsPrec :: Int -> DeleteTableResult -> String -> String
$cshow :: DeleteTableResult -> String
show :: DeleteTableResult -> String
$cshowList :: [DeleteTableResult] -> String -> String
showList :: [DeleteTableResult] -> String -> String
Show, Maybe DeleteTableResult
Value -> Parser [DeleteTableResult]
Value -> Parser DeleteTableResult
(Value -> Parser DeleteTableResult)
-> (Value -> Parser [DeleteTableResult])
-> Maybe DeleteTableResult
-> FromJSON DeleteTableResult
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser DeleteTableResult
parseJSON :: Value -> Parser DeleteTableResult
$cparseJSONList :: Value -> Parser [DeleteTableResult]
parseJSONList :: Value -> Parser [DeleteTableResult]
$comittedField :: Maybe DeleteTableResult
omittedField :: Maybe DeleteTableResult
A.FromJSON)
-- ResponseConsumer can't be derived
instance ResponseConsumer r DeleteTableResult where
    type ResponseMetadata DeleteTableResult = DdbResponse
    responseConsumer :: Request
-> r
-> IORef (ResponseMetadata DeleteTableResult)
-> HTTPResponseConsumer DeleteTableResult
responseConsumer Request
_ r
_ = IORef (ResponseMetadata DeleteTableResult)
-> HTTPResponseConsumer DeleteTableResult
IORef DdbResponse -> HTTPResponseConsumer DeleteTableResult
forall a. FromJSON a => IORef DdbResponse -> HTTPResponseConsumer a
ddbResponseConsumer
instance AsMemoryResponse DeleteTableResult where
    type MemoryResponse DeleteTableResult = TableDescription
    loadToMemory :: DeleteTableResult
-> ResourceT IO (MemoryResponse DeleteTableResult)
loadToMemory = TableDescription -> ResourceT IO TableDescription
forall a. a -> ResourceT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (TableDescription -> ResourceT IO TableDescription)
-> (DeleteTableResult -> TableDescription)
-> DeleteTableResult
-> ResourceT IO TableDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DeleteTableResult -> TableDescription
dStatus

instance Transaction DeleteTable DeleteTableResult

-- | TODO: currently this does not support restarting a cutoff query because of size.
data ListTables = ListTables
    deriving (Int -> ListTables -> String -> String
[ListTables] -> String -> String
ListTables -> String
(Int -> ListTables -> String -> String)
-> (ListTables -> String)
-> ([ListTables] -> String -> String)
-> Show ListTables
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ListTables -> String -> String
showsPrec :: Int -> ListTables -> String -> String
$cshow :: ListTables -> String
show :: ListTables -> String
$cshowList :: [ListTables] -> String -> String
showList :: [ListTables] -> String -> String
Show)
instance A.ToJSON ListTables where
    toJSON :: ListTables -> Value
toJSON ListTables
_ = [Pair] -> Value
A.object []
-- | ServiceConfiguration: 'DdbConfiguration'
instance SignQuery ListTables where
    type ServiceConfiguration ListTables = DdbConfiguration
    signQuery :: forall queryType.
ListTables
-> ServiceConfiguration ListTables queryType
-> SignatureData
-> SignedQuery
signQuery = ByteString
-> ListTables
-> DdbConfiguration queryType
-> SignatureData
-> SignedQuery
forall a qt.
ToJSON a =>
ByteString
-> a -> DdbConfiguration qt -> SignatureData -> SignedQuery
ddbSignQuery ByteString
"ListTables"

newtype ListTablesResult
    = ListTablesResult {
        ListTablesResult -> [Text]
tableNames :: [T.Text]
      }
    deriving (Int -> ListTablesResult -> String -> String
[ListTablesResult] -> String -> String
ListTablesResult -> String
(Int -> ListTablesResult -> String -> String)
-> (ListTablesResult -> String)
-> ([ListTablesResult] -> String -> String)
-> Show ListTablesResult
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ListTablesResult -> String -> String
showsPrec :: Int -> ListTablesResult -> String -> String
$cshow :: ListTablesResult -> String
show :: ListTablesResult -> String
$cshowList :: [ListTablesResult] -> String -> String
showList :: [ListTablesResult] -> String -> String
Show, (forall x. ListTablesResult -> Rep ListTablesResult x)
-> (forall x. Rep ListTablesResult x -> ListTablesResult)
-> Generic ListTablesResult
forall x. Rep ListTablesResult x -> ListTablesResult
forall x. ListTablesResult -> Rep ListTablesResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ListTablesResult -> Rep ListTablesResult x
from :: forall x. ListTablesResult -> Rep ListTablesResult x
$cto :: forall x. Rep ListTablesResult x -> ListTablesResult
to :: forall x. Rep ListTablesResult x -> ListTablesResult
Generic)
instance A.FromJSON ListTablesResult where
    parseJSON :: Value -> Parser ListTablesResult
parseJSON = Options -> Value -> Parser ListTablesResult
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
A.genericParseJSON Options
capitalizeOpt
instance ResponseConsumer r ListTablesResult where
    type ResponseMetadata ListTablesResult = DdbResponse
    responseConsumer :: Request
-> r
-> IORef (ResponseMetadata ListTablesResult)
-> HTTPResponseConsumer ListTablesResult
responseConsumer Request
_ r
_ = IORef (ResponseMetadata ListTablesResult)
-> HTTPResponseConsumer ListTablesResult
IORef DdbResponse -> HTTPResponseConsumer ListTablesResult
forall a. FromJSON a => IORef DdbResponse -> HTTPResponseConsumer a
ddbResponseConsumer
instance AsMemoryResponse ListTablesResult where
    type MemoryResponse ListTablesResult = [T.Text]
    loadToMemory :: ListTablesResult -> ResourceT IO (MemoryResponse ListTablesResult)
loadToMemory = [Text] -> ResourceT IO [Text]
forall a. a -> ResourceT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Text] -> ResourceT IO [Text])
-> (ListTablesResult -> [Text])
-> ListTablesResult
-> ResourceT IO [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ListTablesResult -> [Text]
tableNames

instance Transaction ListTables ListTablesResult