{-# 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.Location.UpdatePlaceIndex
(
UpdatePlaceIndex (..),
newUpdatePlaceIndex,
updatePlaceIndex_dataSourceConfiguration,
updatePlaceIndex_description,
updatePlaceIndex_pricingPlan,
updatePlaceIndex_indexName,
UpdatePlaceIndexResponse (..),
newUpdatePlaceIndexResponse,
updatePlaceIndexResponse_httpStatus,
updatePlaceIndexResponse_indexArn,
updatePlaceIndexResponse_indexName,
updatePlaceIndexResponse_updateTime,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Location.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data UpdatePlaceIndex = UpdatePlaceIndex'
{
UpdatePlaceIndex -> Maybe DataSourceConfiguration
dataSourceConfiguration :: Prelude.Maybe DataSourceConfiguration,
UpdatePlaceIndex -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
UpdatePlaceIndex -> Maybe PricingPlan
pricingPlan :: Prelude.Maybe PricingPlan,
UpdatePlaceIndex -> Text
indexName :: Prelude.Text
}
deriving (UpdatePlaceIndex -> UpdatePlaceIndex -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdatePlaceIndex -> UpdatePlaceIndex -> Bool
$c/= :: UpdatePlaceIndex -> UpdatePlaceIndex -> Bool
== :: UpdatePlaceIndex -> UpdatePlaceIndex -> Bool
$c== :: UpdatePlaceIndex -> UpdatePlaceIndex -> Bool
Prelude.Eq, ReadPrec [UpdatePlaceIndex]
ReadPrec UpdatePlaceIndex
Int -> ReadS UpdatePlaceIndex
ReadS [UpdatePlaceIndex]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdatePlaceIndex]
$creadListPrec :: ReadPrec [UpdatePlaceIndex]
readPrec :: ReadPrec UpdatePlaceIndex
$creadPrec :: ReadPrec UpdatePlaceIndex
readList :: ReadS [UpdatePlaceIndex]
$creadList :: ReadS [UpdatePlaceIndex]
readsPrec :: Int -> ReadS UpdatePlaceIndex
$creadsPrec :: Int -> ReadS UpdatePlaceIndex
Prelude.Read, Int -> UpdatePlaceIndex -> ShowS
[UpdatePlaceIndex] -> ShowS
UpdatePlaceIndex -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdatePlaceIndex] -> ShowS
$cshowList :: [UpdatePlaceIndex] -> ShowS
show :: UpdatePlaceIndex -> String
$cshow :: UpdatePlaceIndex -> String
showsPrec :: Int -> UpdatePlaceIndex -> ShowS
$cshowsPrec :: Int -> UpdatePlaceIndex -> ShowS
Prelude.Show, forall x. Rep UpdatePlaceIndex x -> UpdatePlaceIndex
forall x. UpdatePlaceIndex -> Rep UpdatePlaceIndex x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdatePlaceIndex x -> UpdatePlaceIndex
$cfrom :: forall x. UpdatePlaceIndex -> Rep UpdatePlaceIndex x
Prelude.Generic)
newUpdatePlaceIndex ::
Prelude.Text ->
UpdatePlaceIndex
newUpdatePlaceIndex :: Text -> UpdatePlaceIndex
newUpdatePlaceIndex Text
pIndexName_ =
UpdatePlaceIndex'
{ $sel:dataSourceConfiguration:UpdatePlaceIndex' :: Maybe DataSourceConfiguration
dataSourceConfiguration =
forall a. Maybe a
Prelude.Nothing,
$sel:description:UpdatePlaceIndex' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
$sel:pricingPlan:UpdatePlaceIndex' :: Maybe PricingPlan
pricingPlan = forall a. Maybe a
Prelude.Nothing,
$sel:indexName:UpdatePlaceIndex' :: Text
indexName = Text
pIndexName_
}
updatePlaceIndex_dataSourceConfiguration :: Lens.Lens' UpdatePlaceIndex (Prelude.Maybe DataSourceConfiguration)
updatePlaceIndex_dataSourceConfiguration :: Lens' UpdatePlaceIndex (Maybe DataSourceConfiguration)
updatePlaceIndex_dataSourceConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePlaceIndex' {Maybe DataSourceConfiguration
dataSourceConfiguration :: Maybe DataSourceConfiguration
$sel:dataSourceConfiguration:UpdatePlaceIndex' :: UpdatePlaceIndex -> Maybe DataSourceConfiguration
dataSourceConfiguration} -> Maybe DataSourceConfiguration
dataSourceConfiguration) (\s :: UpdatePlaceIndex
s@UpdatePlaceIndex' {} Maybe DataSourceConfiguration
a -> UpdatePlaceIndex
s {$sel:dataSourceConfiguration:UpdatePlaceIndex' :: Maybe DataSourceConfiguration
dataSourceConfiguration = Maybe DataSourceConfiguration
a} :: UpdatePlaceIndex)
updatePlaceIndex_description :: Lens.Lens' UpdatePlaceIndex (Prelude.Maybe Prelude.Text)
updatePlaceIndex_description :: Lens' UpdatePlaceIndex (Maybe Text)
updatePlaceIndex_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePlaceIndex' {Maybe Text
description :: Maybe Text
$sel:description:UpdatePlaceIndex' :: UpdatePlaceIndex -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdatePlaceIndex
s@UpdatePlaceIndex' {} Maybe Text
a -> UpdatePlaceIndex
s {$sel:description:UpdatePlaceIndex' :: Maybe Text
description = Maybe Text
a} :: UpdatePlaceIndex)
updatePlaceIndex_pricingPlan :: Lens.Lens' UpdatePlaceIndex (Prelude.Maybe PricingPlan)
updatePlaceIndex_pricingPlan :: Lens' UpdatePlaceIndex (Maybe PricingPlan)
updatePlaceIndex_pricingPlan = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePlaceIndex' {Maybe PricingPlan
pricingPlan :: Maybe PricingPlan
$sel:pricingPlan:UpdatePlaceIndex' :: UpdatePlaceIndex -> Maybe PricingPlan
pricingPlan} -> Maybe PricingPlan
pricingPlan) (\s :: UpdatePlaceIndex
s@UpdatePlaceIndex' {} Maybe PricingPlan
a -> UpdatePlaceIndex
s {$sel:pricingPlan:UpdatePlaceIndex' :: Maybe PricingPlan
pricingPlan = Maybe PricingPlan
a} :: UpdatePlaceIndex)
updatePlaceIndex_indexName :: Lens.Lens' UpdatePlaceIndex Prelude.Text
updatePlaceIndex_indexName :: Lens' UpdatePlaceIndex Text
updatePlaceIndex_indexName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePlaceIndex' {Text
indexName :: Text
$sel:indexName:UpdatePlaceIndex' :: UpdatePlaceIndex -> Text
indexName} -> Text
indexName) (\s :: UpdatePlaceIndex
s@UpdatePlaceIndex' {} Text
a -> UpdatePlaceIndex
s {$sel:indexName:UpdatePlaceIndex' :: Text
indexName = Text
a} :: UpdatePlaceIndex)
instance Core.AWSRequest UpdatePlaceIndex where
type
AWSResponse UpdatePlaceIndex =
UpdatePlaceIndexResponse
request :: (Service -> Service)
-> UpdatePlaceIndex -> Request UpdatePlaceIndex
request Service -> Service
overrides =
forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.patchJSON (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdatePlaceIndex
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdatePlaceIndex)))
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 ->
Int -> Text -> Text -> ISO8601 -> UpdatePlaceIndexResponse
UpdatePlaceIndexResponse'
forall (f :: * -> *) a b. Functor 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))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"IndexArn")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"IndexName")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"UpdateTime")
)
instance Prelude.Hashable UpdatePlaceIndex where
hashWithSalt :: Int -> UpdatePlaceIndex -> Int
hashWithSalt Int
_salt UpdatePlaceIndex' {Maybe Text
Maybe DataSourceConfiguration
Maybe PricingPlan
Text
indexName :: Text
pricingPlan :: Maybe PricingPlan
description :: Maybe Text
dataSourceConfiguration :: Maybe DataSourceConfiguration
$sel:indexName:UpdatePlaceIndex' :: UpdatePlaceIndex -> Text
$sel:pricingPlan:UpdatePlaceIndex' :: UpdatePlaceIndex -> Maybe PricingPlan
$sel:description:UpdatePlaceIndex' :: UpdatePlaceIndex -> Maybe Text
$sel:dataSourceConfiguration:UpdatePlaceIndex' :: UpdatePlaceIndex -> Maybe DataSourceConfiguration
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DataSourceConfiguration
dataSourceConfiguration
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PricingPlan
pricingPlan
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
indexName
instance Prelude.NFData UpdatePlaceIndex where
rnf :: UpdatePlaceIndex -> ()
rnf UpdatePlaceIndex' {Maybe Text
Maybe DataSourceConfiguration
Maybe PricingPlan
Text
indexName :: Text
pricingPlan :: Maybe PricingPlan
description :: Maybe Text
dataSourceConfiguration :: Maybe DataSourceConfiguration
$sel:indexName:UpdatePlaceIndex' :: UpdatePlaceIndex -> Text
$sel:pricingPlan:UpdatePlaceIndex' :: UpdatePlaceIndex -> Maybe PricingPlan
$sel:description:UpdatePlaceIndex' :: UpdatePlaceIndex -> Maybe Text
$sel:dataSourceConfiguration:UpdatePlaceIndex' :: UpdatePlaceIndex -> Maybe DataSourceConfiguration
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe DataSourceConfiguration
dataSourceConfiguration
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PricingPlan
pricingPlan
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
indexName
instance Data.ToHeaders UpdatePlaceIndex where
toHeaders :: UpdatePlaceIndex -> ResponseHeaders
toHeaders =
forall a b. a -> b -> a
Prelude.const
( forall a. Monoid a => [a] -> a
Prelude.mconcat
[ HeaderName
"Content-Type"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
Prelude.ByteString
)
]
)
instance Data.ToJSON UpdatePlaceIndex where
toJSON :: UpdatePlaceIndex -> Value
toJSON UpdatePlaceIndex' {Maybe Text
Maybe DataSourceConfiguration
Maybe PricingPlan
Text
indexName :: Text
pricingPlan :: Maybe PricingPlan
description :: Maybe Text
dataSourceConfiguration :: Maybe DataSourceConfiguration
$sel:indexName:UpdatePlaceIndex' :: UpdatePlaceIndex -> Text
$sel:pricingPlan:UpdatePlaceIndex' :: UpdatePlaceIndex -> Maybe PricingPlan
$sel:description:UpdatePlaceIndex' :: UpdatePlaceIndex -> Maybe Text
$sel:dataSourceConfiguration:UpdatePlaceIndex' :: UpdatePlaceIndex -> Maybe DataSourceConfiguration
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"DataSourceConfiguration" 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 DataSourceConfiguration
dataSourceConfiguration,
(Key
"Description" 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
description,
(Key
"PricingPlan" 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 PricingPlan
pricingPlan
]
)
instance Data.ToPath UpdatePlaceIndex where
toPath :: UpdatePlaceIndex -> ByteString
toPath UpdatePlaceIndex' {Maybe Text
Maybe DataSourceConfiguration
Maybe PricingPlan
Text
indexName :: Text
pricingPlan :: Maybe PricingPlan
description :: Maybe Text
dataSourceConfiguration :: Maybe DataSourceConfiguration
$sel:indexName:UpdatePlaceIndex' :: UpdatePlaceIndex -> Text
$sel:pricingPlan:UpdatePlaceIndex' :: UpdatePlaceIndex -> Maybe PricingPlan
$sel:description:UpdatePlaceIndex' :: UpdatePlaceIndex -> Maybe Text
$sel:dataSourceConfiguration:UpdatePlaceIndex' :: UpdatePlaceIndex -> Maybe DataSourceConfiguration
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ByteString
"/places/v0/indexes/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
indexName]
instance Data.ToQuery UpdatePlaceIndex where
toQuery :: UpdatePlaceIndex -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data UpdatePlaceIndexResponse = UpdatePlaceIndexResponse'
{
UpdatePlaceIndexResponse -> Int
httpStatus :: Prelude.Int,
UpdatePlaceIndexResponse -> Text
indexArn :: Prelude.Text,
UpdatePlaceIndexResponse -> Text
indexName :: Prelude.Text,
UpdatePlaceIndexResponse -> ISO8601
updateTime :: Data.ISO8601
}
deriving (UpdatePlaceIndexResponse -> UpdatePlaceIndexResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdatePlaceIndexResponse -> UpdatePlaceIndexResponse -> Bool
$c/= :: UpdatePlaceIndexResponse -> UpdatePlaceIndexResponse -> Bool
== :: UpdatePlaceIndexResponse -> UpdatePlaceIndexResponse -> Bool
$c== :: UpdatePlaceIndexResponse -> UpdatePlaceIndexResponse -> Bool
Prelude.Eq, ReadPrec [UpdatePlaceIndexResponse]
ReadPrec UpdatePlaceIndexResponse
Int -> ReadS UpdatePlaceIndexResponse
ReadS [UpdatePlaceIndexResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdatePlaceIndexResponse]
$creadListPrec :: ReadPrec [UpdatePlaceIndexResponse]
readPrec :: ReadPrec UpdatePlaceIndexResponse
$creadPrec :: ReadPrec UpdatePlaceIndexResponse
readList :: ReadS [UpdatePlaceIndexResponse]
$creadList :: ReadS [UpdatePlaceIndexResponse]
readsPrec :: Int -> ReadS UpdatePlaceIndexResponse
$creadsPrec :: Int -> ReadS UpdatePlaceIndexResponse
Prelude.Read, Int -> UpdatePlaceIndexResponse -> ShowS
[UpdatePlaceIndexResponse] -> ShowS
UpdatePlaceIndexResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdatePlaceIndexResponse] -> ShowS
$cshowList :: [UpdatePlaceIndexResponse] -> ShowS
show :: UpdatePlaceIndexResponse -> String
$cshow :: UpdatePlaceIndexResponse -> String
showsPrec :: Int -> UpdatePlaceIndexResponse -> ShowS
$cshowsPrec :: Int -> UpdatePlaceIndexResponse -> ShowS
Prelude.Show, forall x.
Rep UpdatePlaceIndexResponse x -> UpdatePlaceIndexResponse
forall x.
UpdatePlaceIndexResponse -> Rep UpdatePlaceIndexResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdatePlaceIndexResponse x -> UpdatePlaceIndexResponse
$cfrom :: forall x.
UpdatePlaceIndexResponse -> Rep UpdatePlaceIndexResponse x
Prelude.Generic)
newUpdatePlaceIndexResponse ::
Prelude.Int ->
Prelude.Text ->
Prelude.Text ->
Prelude.UTCTime ->
UpdatePlaceIndexResponse
newUpdatePlaceIndexResponse :: Int -> Text -> Text -> UTCTime -> UpdatePlaceIndexResponse
newUpdatePlaceIndexResponse
Int
pHttpStatus_
Text
pIndexArn_
Text
pIndexName_
UTCTime
pUpdateTime_ =
UpdatePlaceIndexResponse'
{ $sel:httpStatus:UpdatePlaceIndexResponse' :: Int
httpStatus =
Int
pHttpStatus_,
$sel:indexArn:UpdatePlaceIndexResponse' :: Text
indexArn = Text
pIndexArn_,
$sel:indexName:UpdatePlaceIndexResponse' :: Text
indexName = Text
pIndexName_,
$sel:updateTime:UpdatePlaceIndexResponse' :: ISO8601
updateTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pUpdateTime_
}
updatePlaceIndexResponse_httpStatus :: Lens.Lens' UpdatePlaceIndexResponse Prelude.Int
updatePlaceIndexResponse_httpStatus :: Lens' UpdatePlaceIndexResponse Int
updatePlaceIndexResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePlaceIndexResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdatePlaceIndexResponse' :: UpdatePlaceIndexResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdatePlaceIndexResponse
s@UpdatePlaceIndexResponse' {} Int
a -> UpdatePlaceIndexResponse
s {$sel:httpStatus:UpdatePlaceIndexResponse' :: Int
httpStatus = Int
a} :: UpdatePlaceIndexResponse)
updatePlaceIndexResponse_indexArn :: Lens.Lens' UpdatePlaceIndexResponse Prelude.Text
updatePlaceIndexResponse_indexArn :: Lens' UpdatePlaceIndexResponse Text
updatePlaceIndexResponse_indexArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePlaceIndexResponse' {Text
indexArn :: Text
$sel:indexArn:UpdatePlaceIndexResponse' :: UpdatePlaceIndexResponse -> Text
indexArn} -> Text
indexArn) (\s :: UpdatePlaceIndexResponse
s@UpdatePlaceIndexResponse' {} Text
a -> UpdatePlaceIndexResponse
s {$sel:indexArn:UpdatePlaceIndexResponse' :: Text
indexArn = Text
a} :: UpdatePlaceIndexResponse)
updatePlaceIndexResponse_indexName :: Lens.Lens' UpdatePlaceIndexResponse Prelude.Text
updatePlaceIndexResponse_indexName :: Lens' UpdatePlaceIndexResponse Text
updatePlaceIndexResponse_indexName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePlaceIndexResponse' {Text
indexName :: Text
$sel:indexName:UpdatePlaceIndexResponse' :: UpdatePlaceIndexResponse -> Text
indexName} -> Text
indexName) (\s :: UpdatePlaceIndexResponse
s@UpdatePlaceIndexResponse' {} Text
a -> UpdatePlaceIndexResponse
s {$sel:indexName:UpdatePlaceIndexResponse' :: Text
indexName = Text
a} :: UpdatePlaceIndexResponse)
updatePlaceIndexResponse_updateTime :: Lens.Lens' UpdatePlaceIndexResponse Prelude.UTCTime
updatePlaceIndexResponse_updateTime :: Lens' UpdatePlaceIndexResponse UTCTime
updatePlaceIndexResponse_updateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePlaceIndexResponse' {ISO8601
updateTime :: ISO8601
$sel:updateTime:UpdatePlaceIndexResponse' :: UpdatePlaceIndexResponse -> ISO8601
updateTime} -> ISO8601
updateTime) (\s :: UpdatePlaceIndexResponse
s@UpdatePlaceIndexResponse' {} ISO8601
a -> UpdatePlaceIndexResponse
s {$sel:updateTime:UpdatePlaceIndexResponse' :: ISO8601
updateTime = ISO8601
a} :: UpdatePlaceIndexResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time
instance Prelude.NFData UpdatePlaceIndexResponse where
rnf :: UpdatePlaceIndexResponse -> ()
rnf UpdatePlaceIndexResponse' {Int
Text
ISO8601
updateTime :: ISO8601
indexName :: Text
indexArn :: Text
httpStatus :: Int
$sel:updateTime:UpdatePlaceIndexResponse' :: UpdatePlaceIndexResponse -> ISO8601
$sel:indexName:UpdatePlaceIndexResponse' :: UpdatePlaceIndexResponse -> Text
$sel:indexArn:UpdatePlaceIndexResponse' :: UpdatePlaceIndexResponse -> Text
$sel:httpStatus:UpdatePlaceIndexResponse' :: UpdatePlaceIndexResponse -> Int
..} =
forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
indexArn
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
indexName
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ISO8601
updateTime