{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}
module Amazonka.DynamoDB.ListGlobalTables
(
ListGlobalTables (..),
newListGlobalTables,
listGlobalTables_exclusiveStartGlobalTableName,
listGlobalTables_limit,
listGlobalTables_regionName,
ListGlobalTablesResponse (..),
newListGlobalTablesResponse,
listGlobalTablesResponse_globalTables,
listGlobalTablesResponse_lastEvaluatedGlobalTableName,
listGlobalTablesResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.DynamoDB.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data ListGlobalTables = ListGlobalTables'
{
ListGlobalTables -> Maybe Text
exclusiveStartGlobalTableName :: Prelude.Maybe Prelude.Text,
ListGlobalTables -> Maybe Natural
limit :: Prelude.Maybe Prelude.Natural,
ListGlobalTables -> Maybe Text
regionName :: Prelude.Maybe Prelude.Text
}
deriving (ListGlobalTables -> ListGlobalTables -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListGlobalTables -> ListGlobalTables -> Bool
$c/= :: ListGlobalTables -> ListGlobalTables -> Bool
== :: ListGlobalTables -> ListGlobalTables -> Bool
$c== :: ListGlobalTables -> ListGlobalTables -> Bool
Prelude.Eq, ReadPrec [ListGlobalTables]
ReadPrec ListGlobalTables
Int -> ReadS ListGlobalTables
ReadS [ListGlobalTables]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListGlobalTables]
$creadListPrec :: ReadPrec [ListGlobalTables]
readPrec :: ReadPrec ListGlobalTables
$creadPrec :: ReadPrec ListGlobalTables
readList :: ReadS [ListGlobalTables]
$creadList :: ReadS [ListGlobalTables]
readsPrec :: Int -> ReadS ListGlobalTables
$creadsPrec :: Int -> ReadS ListGlobalTables
Prelude.Read, Int -> ListGlobalTables -> ShowS
[ListGlobalTables] -> ShowS
ListGlobalTables -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListGlobalTables] -> ShowS
$cshowList :: [ListGlobalTables] -> ShowS
show :: ListGlobalTables -> String
$cshow :: ListGlobalTables -> String
showsPrec :: Int -> ListGlobalTables -> ShowS
$cshowsPrec :: Int -> ListGlobalTables -> ShowS
Prelude.Show, forall x. Rep ListGlobalTables x -> ListGlobalTables
forall x. ListGlobalTables -> Rep ListGlobalTables x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListGlobalTables x -> ListGlobalTables
$cfrom :: forall x. ListGlobalTables -> Rep ListGlobalTables x
Prelude.Generic)
newListGlobalTables ::
ListGlobalTables
newListGlobalTables :: ListGlobalTables
newListGlobalTables =
ListGlobalTables'
{ $sel:exclusiveStartGlobalTableName:ListGlobalTables' :: Maybe Text
exclusiveStartGlobalTableName =
forall a. Maybe a
Prelude.Nothing,
$sel:limit:ListGlobalTables' :: Maybe Natural
limit = forall a. Maybe a
Prelude.Nothing,
$sel:regionName:ListGlobalTables' :: Maybe Text
regionName = forall a. Maybe a
Prelude.Nothing
}
listGlobalTables_exclusiveStartGlobalTableName :: Lens.Lens' ListGlobalTables (Prelude.Maybe Prelude.Text)
listGlobalTables_exclusiveStartGlobalTableName :: Lens' ListGlobalTables (Maybe Text)
listGlobalTables_exclusiveStartGlobalTableName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListGlobalTables' {Maybe Text
exclusiveStartGlobalTableName :: Maybe Text
$sel:exclusiveStartGlobalTableName:ListGlobalTables' :: ListGlobalTables -> Maybe Text
exclusiveStartGlobalTableName} -> Maybe Text
exclusiveStartGlobalTableName) (\s :: ListGlobalTables
s@ListGlobalTables' {} Maybe Text
a -> ListGlobalTables
s {$sel:exclusiveStartGlobalTableName:ListGlobalTables' :: Maybe Text
exclusiveStartGlobalTableName = Maybe Text
a} :: ListGlobalTables)
listGlobalTables_limit :: Lens.Lens' ListGlobalTables (Prelude.Maybe Prelude.Natural)
listGlobalTables_limit :: Lens' ListGlobalTables (Maybe Natural)
listGlobalTables_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListGlobalTables' {Maybe Natural
limit :: Maybe Natural
$sel:limit:ListGlobalTables' :: ListGlobalTables -> Maybe Natural
limit} -> Maybe Natural
limit) (\s :: ListGlobalTables
s@ListGlobalTables' {} Maybe Natural
a -> ListGlobalTables
s {$sel:limit:ListGlobalTables' :: Maybe Natural
limit = Maybe Natural
a} :: ListGlobalTables)
listGlobalTables_regionName :: Lens.Lens' ListGlobalTables (Prelude.Maybe Prelude.Text)
listGlobalTables_regionName :: Lens' ListGlobalTables (Maybe Text)
listGlobalTables_regionName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListGlobalTables' {Maybe Text
regionName :: Maybe Text
$sel:regionName:ListGlobalTables' :: ListGlobalTables -> Maybe Text
regionName} -> Maybe Text
regionName) (\s :: ListGlobalTables
s@ListGlobalTables' {} Maybe Text
a -> ListGlobalTables
s {$sel:regionName:ListGlobalTables' :: Maybe Text
regionName = Maybe Text
a} :: ListGlobalTables)
instance Core.AWSRequest ListGlobalTables where
type
AWSResponse ListGlobalTables =
ListGlobalTablesResponse
request :: (Service -> Service)
-> ListGlobalTables -> Request ListGlobalTables
request Service -> Service
overrides =
forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ListGlobalTables
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListGlobalTables)))
response =
forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
( \Int
s ResponseHeaders
h Object
x ->
Maybe [GlobalTable]
-> Maybe Text -> Int -> ListGlobalTablesResponse
ListGlobalTablesResponse'
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"GlobalTables" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"LastEvaluatedGlobalTableName")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
)
instance Prelude.Hashable ListGlobalTables where
hashWithSalt :: Int -> ListGlobalTables -> Int
hashWithSalt Int
_salt ListGlobalTables' {Maybe Natural
Maybe Text
regionName :: Maybe Text
limit :: Maybe Natural
exclusiveStartGlobalTableName :: Maybe Text
$sel:regionName:ListGlobalTables' :: ListGlobalTables -> Maybe Text
$sel:limit:ListGlobalTables' :: ListGlobalTables -> Maybe Natural
$sel:exclusiveStartGlobalTableName:ListGlobalTables' :: ListGlobalTables -> Maybe Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
exclusiveStartGlobalTableName
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
limit
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
regionName
instance Prelude.NFData ListGlobalTables where
rnf :: ListGlobalTables -> ()
rnf ListGlobalTables' {Maybe Natural
Maybe Text
regionName :: Maybe Text
limit :: Maybe Natural
exclusiveStartGlobalTableName :: Maybe Text
$sel:regionName:ListGlobalTables' :: ListGlobalTables -> Maybe Text
$sel:limit:ListGlobalTables' :: ListGlobalTables -> Maybe Natural
$sel:exclusiveStartGlobalTableName:ListGlobalTables' :: ListGlobalTables -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
exclusiveStartGlobalTableName
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
limit
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
regionName
instance Data.ToHeaders ListGlobalTables where
toHeaders :: ListGlobalTables -> ResponseHeaders
toHeaders =
forall a b. a -> b -> a
Prelude.const
( forall a. Monoid a => [a] -> a
Prelude.mconcat
[ HeaderName
"X-Amz-Target"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"DynamoDB_20120810.ListGlobalTables" ::
Prelude.ByteString
),
HeaderName
"Content-Type"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
Prelude.ByteString
)
]
)
instance Data.ToJSON ListGlobalTables where
toJSON :: ListGlobalTables -> Value
toJSON ListGlobalTables' {Maybe Natural
Maybe Text
regionName :: Maybe Text
limit :: Maybe Natural
exclusiveStartGlobalTableName :: Maybe Text
$sel:regionName:ListGlobalTables' :: ListGlobalTables -> Maybe Text
$sel:limit:ListGlobalTables' :: ListGlobalTables -> Maybe Natural
$sel:exclusiveStartGlobalTableName:ListGlobalTables' :: ListGlobalTables -> Maybe Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"ExclusiveStartGlobalTableName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
exclusiveStartGlobalTableName,
(Key
"Limit" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
limit,
(Key
"RegionName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
regionName
]
)
instance Data.ToPath ListGlobalTables where
toPath :: ListGlobalTables -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery ListGlobalTables where
toQuery :: ListGlobalTables -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data ListGlobalTablesResponse = ListGlobalTablesResponse'
{
ListGlobalTablesResponse -> Maybe [GlobalTable]
globalTables :: Prelude.Maybe [GlobalTable],
ListGlobalTablesResponse -> Maybe Text
lastEvaluatedGlobalTableName :: Prelude.Maybe Prelude.Text,
ListGlobalTablesResponse -> Int
httpStatus :: Prelude.Int
}
deriving (ListGlobalTablesResponse -> ListGlobalTablesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListGlobalTablesResponse -> ListGlobalTablesResponse -> Bool
$c/= :: ListGlobalTablesResponse -> ListGlobalTablesResponse -> Bool
== :: ListGlobalTablesResponse -> ListGlobalTablesResponse -> Bool
$c== :: ListGlobalTablesResponse -> ListGlobalTablesResponse -> Bool
Prelude.Eq, ReadPrec [ListGlobalTablesResponse]
ReadPrec ListGlobalTablesResponse
Int -> ReadS ListGlobalTablesResponse
ReadS [ListGlobalTablesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListGlobalTablesResponse]
$creadListPrec :: ReadPrec [ListGlobalTablesResponse]
readPrec :: ReadPrec ListGlobalTablesResponse
$creadPrec :: ReadPrec ListGlobalTablesResponse
readList :: ReadS [ListGlobalTablesResponse]
$creadList :: ReadS [ListGlobalTablesResponse]
readsPrec :: Int -> ReadS ListGlobalTablesResponse
$creadsPrec :: Int -> ReadS ListGlobalTablesResponse
Prelude.Read, Int -> ListGlobalTablesResponse -> ShowS
[ListGlobalTablesResponse] -> ShowS
ListGlobalTablesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListGlobalTablesResponse] -> ShowS
$cshowList :: [ListGlobalTablesResponse] -> ShowS
show :: ListGlobalTablesResponse -> String
$cshow :: ListGlobalTablesResponse -> String
showsPrec :: Int -> ListGlobalTablesResponse -> ShowS
$cshowsPrec :: Int -> ListGlobalTablesResponse -> ShowS
Prelude.Show, forall x.
Rep ListGlobalTablesResponse x -> ListGlobalTablesResponse
forall x.
ListGlobalTablesResponse -> Rep ListGlobalTablesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListGlobalTablesResponse x -> ListGlobalTablesResponse
$cfrom :: forall x.
ListGlobalTablesResponse -> Rep ListGlobalTablesResponse x
Prelude.Generic)
newListGlobalTablesResponse ::
Prelude.Int ->
ListGlobalTablesResponse
newListGlobalTablesResponse :: Int -> ListGlobalTablesResponse
newListGlobalTablesResponse Int
pHttpStatus_ =
ListGlobalTablesResponse'
{ $sel:globalTables:ListGlobalTablesResponse' :: Maybe [GlobalTable]
globalTables =
forall a. Maybe a
Prelude.Nothing,
$sel:lastEvaluatedGlobalTableName:ListGlobalTablesResponse' :: Maybe Text
lastEvaluatedGlobalTableName = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:ListGlobalTablesResponse' :: Int
httpStatus = Int
pHttpStatus_
}
listGlobalTablesResponse_globalTables :: Lens.Lens' ListGlobalTablesResponse (Prelude.Maybe [GlobalTable])
listGlobalTablesResponse_globalTables :: Lens' ListGlobalTablesResponse (Maybe [GlobalTable])
listGlobalTablesResponse_globalTables = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListGlobalTablesResponse' {Maybe [GlobalTable]
globalTables :: Maybe [GlobalTable]
$sel:globalTables:ListGlobalTablesResponse' :: ListGlobalTablesResponse -> Maybe [GlobalTable]
globalTables} -> Maybe [GlobalTable]
globalTables) (\s :: ListGlobalTablesResponse
s@ListGlobalTablesResponse' {} Maybe [GlobalTable]
a -> ListGlobalTablesResponse
s {$sel:globalTables:ListGlobalTablesResponse' :: Maybe [GlobalTable]
globalTables = Maybe [GlobalTable]
a} :: ListGlobalTablesResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
listGlobalTablesResponse_lastEvaluatedGlobalTableName :: Lens.Lens' ListGlobalTablesResponse (Prelude.Maybe Prelude.Text)
listGlobalTablesResponse_lastEvaluatedGlobalTableName :: Lens' ListGlobalTablesResponse (Maybe Text)
listGlobalTablesResponse_lastEvaluatedGlobalTableName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListGlobalTablesResponse' {Maybe Text
lastEvaluatedGlobalTableName :: Maybe Text
$sel:lastEvaluatedGlobalTableName:ListGlobalTablesResponse' :: ListGlobalTablesResponse -> Maybe Text
lastEvaluatedGlobalTableName} -> Maybe Text
lastEvaluatedGlobalTableName) (\s :: ListGlobalTablesResponse
s@ListGlobalTablesResponse' {} Maybe Text
a -> ListGlobalTablesResponse
s {$sel:lastEvaluatedGlobalTableName:ListGlobalTablesResponse' :: Maybe Text
lastEvaluatedGlobalTableName = Maybe Text
a} :: ListGlobalTablesResponse)
listGlobalTablesResponse_httpStatus :: Lens.Lens' ListGlobalTablesResponse Prelude.Int
listGlobalTablesResponse_httpStatus :: Lens' ListGlobalTablesResponse Int
listGlobalTablesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListGlobalTablesResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListGlobalTablesResponse' :: ListGlobalTablesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListGlobalTablesResponse
s@ListGlobalTablesResponse' {} Int
a -> ListGlobalTablesResponse
s {$sel:httpStatus:ListGlobalTablesResponse' :: Int
httpStatus = Int
a} :: ListGlobalTablesResponse)
instance Prelude.NFData ListGlobalTablesResponse where
rnf :: ListGlobalTablesResponse -> ()
rnf ListGlobalTablesResponse' {Int
Maybe [GlobalTable]
Maybe Text
httpStatus :: Int
lastEvaluatedGlobalTableName :: Maybe Text
globalTables :: Maybe [GlobalTable]
$sel:httpStatus:ListGlobalTablesResponse' :: ListGlobalTablesResponse -> Int
$sel:lastEvaluatedGlobalTableName:ListGlobalTablesResponse' :: ListGlobalTablesResponse -> Maybe Text
$sel:globalTables:ListGlobalTablesResponse' :: ListGlobalTablesResponse -> Maybe [GlobalTable]
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe [GlobalTable]
globalTables
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
lastEvaluatedGlobalTableName
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus