{-# 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 #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.ResourceExplorer2.UpdateIndexType
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Changes the type of the index from one of the following types to the
-- other. For more information about indexes and the role they perform in
-- Amazon Web Services Resource Explorer, see
-- <https://docs.aws.amazon.com/resource-explorer/latest/userguide/manage-aggregator-region.html Turning on cross-Region search by creating an aggregator index>
-- in the /Amazon Web Services Resource Explorer User Guide/.
--
-- -   __@AGGREGATOR@ index type__
--
--     The index contains information about resources from all Amazon Web
--     Services Regions in the Amazon Web Services account in which you\'ve
--     created a Resource Explorer index. Resource information from all
--     other Regions is replicated to this Region\'s index.
--
--     When you change the index type to @AGGREGATOR@, Resource Explorer
--     turns on replication of all discovered resource information from the
--     other Amazon Web Services Regions in your account to this index. You
--     can then, from this Region only, perform resource search queries
--     that span all Amazon Web Services Regions in the Amazon Web Services
--     account. Turning on replication from all other Regions is performed
--     by asynchronous background tasks. You can check the status of the
--     asynchronous tasks by using the GetIndex operation. When the
--     asynchronous tasks complete, the @Status@ response of that operation
--     changes from @UPDATING@ to @ACTIVE@. After that, you can start to
--     see results from other Amazon Web Services Regions in query results.
--     However, it can take several hours for replication from all other
--     Regions to complete.
--
--     You can have only one aggregator index per Amazon Web Services
--     account. Before you can promote a different index to be the
--     aggregator index for the account, you must first demote the existing
--     aggregator index to type @LOCAL@.
--
-- -   __@LOCAL@ index type__
--
--     The index contains information about resources in only the Amazon
--     Web Services Region in which the index exists. If an aggregator
--     index in another Region exists, then information in this local index
--     is replicated to the aggregator index.
--
--     When you change the index type to @LOCAL@, Resource Explorer turns
--     off the replication of resource information from all other Amazon
--     Web Services Regions in the Amazon Web Services account to this
--     Region. The aggregator index remains in the @UPDATING@ state until
--     all replication with other Regions successfully stops. You can check
--     the status of the asynchronous task by using the GetIndex operation.
--     When Resource Explorer successfully stops all replication with other
--     Regions, the @Status@ response of that operation changes from
--     @UPDATING@ to @ACTIVE@. Separately, the resource information from
--     other Regions that was previously stored in the index is deleted
--     within 30 days by another background task. Until that asynchronous
--     task completes, some results from other Regions can continue to
--     appear in search results.
--
--     After you demote an aggregator index to a local index, you must wait
--     24 hours before you can promote another index to be the new
--     aggregator index for the account.
module Amazonka.ResourceExplorer2.UpdateIndexType
  ( -- * Creating a Request
    UpdateIndexType (..),
    newUpdateIndexType,

    -- * Request Lenses
    updateIndexType_arn,
    updateIndexType_type,

    -- * Destructuring the Response
    UpdateIndexTypeResponse (..),
    newUpdateIndexTypeResponse,

    -- * Response Lenses
    updateIndexTypeResponse_arn,
    updateIndexTypeResponse_lastUpdatedAt,
    updateIndexTypeResponse_state,
    updateIndexTypeResponse_type,
    updateIndexTypeResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import Amazonka.ResourceExplorer2.Types
import qualified Amazonka.Response as Response

-- | /See:/ 'newUpdateIndexType' smart constructor.
data UpdateIndexType = UpdateIndexType'
  { -- | The
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon resource name (ARN)>
    -- of the index that you want to update.
    UpdateIndexType -> Text
arn :: Prelude.Text,
    -- | The type of the index. To understand the difference between @LOCAL@ and
    -- @AGGREGATOR@, see
    -- <https://docs.aws.amazon.com/resource-explorer/latest/userguide/manage-aggregator-region.html Turning on cross-Region search>
    -- in the /Amazon Web Services Resource Explorer User Guide/.
    UpdateIndexType -> IndexType
type' :: IndexType
  }
  deriving (UpdateIndexType -> UpdateIndexType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateIndexType -> UpdateIndexType -> Bool
$c/= :: UpdateIndexType -> UpdateIndexType -> Bool
== :: UpdateIndexType -> UpdateIndexType -> Bool
$c== :: UpdateIndexType -> UpdateIndexType -> Bool
Prelude.Eq, ReadPrec [UpdateIndexType]
ReadPrec UpdateIndexType
Int -> ReadS UpdateIndexType
ReadS [UpdateIndexType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateIndexType]
$creadListPrec :: ReadPrec [UpdateIndexType]
readPrec :: ReadPrec UpdateIndexType
$creadPrec :: ReadPrec UpdateIndexType
readList :: ReadS [UpdateIndexType]
$creadList :: ReadS [UpdateIndexType]
readsPrec :: Int -> ReadS UpdateIndexType
$creadsPrec :: Int -> ReadS UpdateIndexType
Prelude.Read, Int -> UpdateIndexType -> ShowS
[UpdateIndexType] -> ShowS
UpdateIndexType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateIndexType] -> ShowS
$cshowList :: [UpdateIndexType] -> ShowS
show :: UpdateIndexType -> String
$cshow :: UpdateIndexType -> String
showsPrec :: Int -> UpdateIndexType -> ShowS
$cshowsPrec :: Int -> UpdateIndexType -> ShowS
Prelude.Show, forall x. Rep UpdateIndexType x -> UpdateIndexType
forall x. UpdateIndexType -> Rep UpdateIndexType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateIndexType x -> UpdateIndexType
$cfrom :: forall x. UpdateIndexType -> Rep UpdateIndexType x
Prelude.Generic)

-- |
-- Create a value of 'UpdateIndexType' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'arn', 'updateIndexType_arn' - The
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon resource name (ARN)>
-- of the index that you want to update.
--
-- 'type'', 'updateIndexType_type' - The type of the index. To understand the difference between @LOCAL@ and
-- @AGGREGATOR@, see
-- <https://docs.aws.amazon.com/resource-explorer/latest/userguide/manage-aggregator-region.html Turning on cross-Region search>
-- in the /Amazon Web Services Resource Explorer User Guide/.
newUpdateIndexType ::
  -- | 'arn'
  Prelude.Text ->
  -- | 'type''
  IndexType ->
  UpdateIndexType
newUpdateIndexType :: Text -> IndexType -> UpdateIndexType
newUpdateIndexType Text
pArn_ IndexType
pType_ =
  UpdateIndexType' {$sel:arn:UpdateIndexType' :: Text
arn = Text
pArn_, $sel:type':UpdateIndexType' :: IndexType
type' = IndexType
pType_}

-- | The
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon resource name (ARN)>
-- of the index that you want to update.
updateIndexType_arn :: Lens.Lens' UpdateIndexType Prelude.Text
updateIndexType_arn :: Lens' UpdateIndexType Text
updateIndexType_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateIndexType' {Text
arn :: Text
$sel:arn:UpdateIndexType' :: UpdateIndexType -> Text
arn} -> Text
arn) (\s :: UpdateIndexType
s@UpdateIndexType' {} Text
a -> UpdateIndexType
s {$sel:arn:UpdateIndexType' :: Text
arn = Text
a} :: UpdateIndexType)

-- | The type of the index. To understand the difference between @LOCAL@ and
-- @AGGREGATOR@, see
-- <https://docs.aws.amazon.com/resource-explorer/latest/userguide/manage-aggregator-region.html Turning on cross-Region search>
-- in the /Amazon Web Services Resource Explorer User Guide/.
updateIndexType_type :: Lens.Lens' UpdateIndexType IndexType
updateIndexType_type :: Lens' UpdateIndexType IndexType
updateIndexType_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateIndexType' {IndexType
type' :: IndexType
$sel:type':UpdateIndexType' :: UpdateIndexType -> IndexType
type'} -> IndexType
type') (\s :: UpdateIndexType
s@UpdateIndexType' {} IndexType
a -> UpdateIndexType
s {$sel:type':UpdateIndexType' :: IndexType
type' = IndexType
a} :: UpdateIndexType)

instance Core.AWSRequest UpdateIndexType where
  type
    AWSResponse UpdateIndexType =
      UpdateIndexTypeResponse
  request :: (Service -> Service) -> UpdateIndexType -> Request UpdateIndexType
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 UpdateIndexType
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateIndexType)))
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 Text
-> Maybe ISO8601
-> Maybe IndexState
-> Maybe IndexType
-> Int
-> UpdateIndexTypeResponse
UpdateIndexTypeResponse'
            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
"Arn")
            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
"LastUpdatedAt")
            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
"State")
            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
"Type")
            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 UpdateIndexType where
  hashWithSalt :: Int -> UpdateIndexType -> Int
hashWithSalt Int
_salt UpdateIndexType' {Text
IndexType
type' :: IndexType
arn :: Text
$sel:type':UpdateIndexType' :: UpdateIndexType -> IndexType
$sel:arn:UpdateIndexType' :: UpdateIndexType -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
arn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` IndexType
type'

instance Prelude.NFData UpdateIndexType where
  rnf :: UpdateIndexType -> ()
rnf UpdateIndexType' {Text
IndexType
type' :: IndexType
arn :: Text
$sel:type':UpdateIndexType' :: UpdateIndexType -> IndexType
$sel:arn:UpdateIndexType' :: UpdateIndexType -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
arn seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf IndexType
type'

instance Data.ToHeaders UpdateIndexType where
  toHeaders :: UpdateIndexType -> 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 UpdateIndexType where
  toJSON :: UpdateIndexType -> Value
toJSON UpdateIndexType' {Text
IndexType
type' :: IndexType
arn :: Text
$sel:type':UpdateIndexType' :: UpdateIndexType -> IndexType
$sel:arn:UpdateIndexType' :: UpdateIndexType -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"Arn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
arn),
            forall a. a -> Maybe a
Prelude.Just (Key
"Type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= IndexType
type')
          ]
      )

instance Data.ToPath UpdateIndexType where
  toPath :: UpdateIndexType -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/UpdateIndexType"

instance Data.ToQuery UpdateIndexType where
  toQuery :: UpdateIndexType -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newUpdateIndexTypeResponse' smart constructor.
data UpdateIndexTypeResponse = UpdateIndexTypeResponse'
  { -- | The
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon resource name (ARN)>
    -- of the index that you updated.
    UpdateIndexTypeResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The date and timestamp when the index was last updated.
    UpdateIndexTypeResponse -> Maybe ISO8601
lastUpdatedAt :: Prelude.Maybe Data.ISO8601,
    -- | Indicates the state of the request to update the index. This operation
    -- is asynchronous. Call the GetIndex operation to check for changes.
    UpdateIndexTypeResponse -> Maybe IndexState
state :: Prelude.Maybe IndexState,
    -- | Specifies the type of the specified index after the operation completes.
    UpdateIndexTypeResponse -> Maybe IndexType
type' :: Prelude.Maybe IndexType,
    -- | The response's http status code.
    UpdateIndexTypeResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateIndexTypeResponse -> UpdateIndexTypeResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateIndexTypeResponse -> UpdateIndexTypeResponse -> Bool
$c/= :: UpdateIndexTypeResponse -> UpdateIndexTypeResponse -> Bool
== :: UpdateIndexTypeResponse -> UpdateIndexTypeResponse -> Bool
$c== :: UpdateIndexTypeResponse -> UpdateIndexTypeResponse -> Bool
Prelude.Eq, ReadPrec [UpdateIndexTypeResponse]
ReadPrec UpdateIndexTypeResponse
Int -> ReadS UpdateIndexTypeResponse
ReadS [UpdateIndexTypeResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateIndexTypeResponse]
$creadListPrec :: ReadPrec [UpdateIndexTypeResponse]
readPrec :: ReadPrec UpdateIndexTypeResponse
$creadPrec :: ReadPrec UpdateIndexTypeResponse
readList :: ReadS [UpdateIndexTypeResponse]
$creadList :: ReadS [UpdateIndexTypeResponse]
readsPrec :: Int -> ReadS UpdateIndexTypeResponse
$creadsPrec :: Int -> ReadS UpdateIndexTypeResponse
Prelude.Read, Int -> UpdateIndexTypeResponse -> ShowS
[UpdateIndexTypeResponse] -> ShowS
UpdateIndexTypeResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateIndexTypeResponse] -> ShowS
$cshowList :: [UpdateIndexTypeResponse] -> ShowS
show :: UpdateIndexTypeResponse -> String
$cshow :: UpdateIndexTypeResponse -> String
showsPrec :: Int -> UpdateIndexTypeResponse -> ShowS
$cshowsPrec :: Int -> UpdateIndexTypeResponse -> ShowS
Prelude.Show, forall x. Rep UpdateIndexTypeResponse x -> UpdateIndexTypeResponse
forall x. UpdateIndexTypeResponse -> Rep UpdateIndexTypeResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateIndexTypeResponse x -> UpdateIndexTypeResponse
$cfrom :: forall x. UpdateIndexTypeResponse -> Rep UpdateIndexTypeResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateIndexTypeResponse' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'arn', 'updateIndexTypeResponse_arn' - The
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon resource name (ARN)>
-- of the index that you updated.
--
-- 'lastUpdatedAt', 'updateIndexTypeResponse_lastUpdatedAt' - The date and timestamp when the index was last updated.
--
-- 'state', 'updateIndexTypeResponse_state' - Indicates the state of the request to update the index. This operation
-- is asynchronous. Call the GetIndex operation to check for changes.
--
-- 'type'', 'updateIndexTypeResponse_type' - Specifies the type of the specified index after the operation completes.
--
-- 'httpStatus', 'updateIndexTypeResponse_httpStatus' - The response's http status code.
newUpdateIndexTypeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateIndexTypeResponse
newUpdateIndexTypeResponse :: Int -> UpdateIndexTypeResponse
newUpdateIndexTypeResponse Int
pHttpStatus_ =
  UpdateIndexTypeResponse'
    { $sel:arn:UpdateIndexTypeResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdatedAt:UpdateIndexTypeResponse' :: Maybe ISO8601
lastUpdatedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:state:UpdateIndexTypeResponse' :: Maybe IndexState
state = forall a. Maybe a
Prelude.Nothing,
      $sel:type':UpdateIndexTypeResponse' :: Maybe IndexType
type' = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateIndexTypeResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon resource name (ARN)>
-- of the index that you updated.
updateIndexTypeResponse_arn :: Lens.Lens' UpdateIndexTypeResponse (Prelude.Maybe Prelude.Text)
updateIndexTypeResponse_arn :: Lens' UpdateIndexTypeResponse (Maybe Text)
updateIndexTypeResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateIndexTypeResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:UpdateIndexTypeResponse' :: UpdateIndexTypeResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: UpdateIndexTypeResponse
s@UpdateIndexTypeResponse' {} Maybe Text
a -> UpdateIndexTypeResponse
s {$sel:arn:UpdateIndexTypeResponse' :: Maybe Text
arn = Maybe Text
a} :: UpdateIndexTypeResponse)

-- | The date and timestamp when the index was last updated.
updateIndexTypeResponse_lastUpdatedAt :: Lens.Lens' UpdateIndexTypeResponse (Prelude.Maybe Prelude.UTCTime)
updateIndexTypeResponse_lastUpdatedAt :: Lens' UpdateIndexTypeResponse (Maybe UTCTime)
updateIndexTypeResponse_lastUpdatedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateIndexTypeResponse' {Maybe ISO8601
lastUpdatedAt :: Maybe ISO8601
$sel:lastUpdatedAt:UpdateIndexTypeResponse' :: UpdateIndexTypeResponse -> Maybe ISO8601
lastUpdatedAt} -> Maybe ISO8601
lastUpdatedAt) (\s :: UpdateIndexTypeResponse
s@UpdateIndexTypeResponse' {} Maybe ISO8601
a -> UpdateIndexTypeResponse
s {$sel:lastUpdatedAt:UpdateIndexTypeResponse' :: Maybe ISO8601
lastUpdatedAt = Maybe ISO8601
a} :: UpdateIndexTypeResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Indicates the state of the request to update the index. This operation
-- is asynchronous. Call the GetIndex operation to check for changes.
updateIndexTypeResponse_state :: Lens.Lens' UpdateIndexTypeResponse (Prelude.Maybe IndexState)
updateIndexTypeResponse_state :: Lens' UpdateIndexTypeResponse (Maybe IndexState)
updateIndexTypeResponse_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateIndexTypeResponse' {Maybe IndexState
state :: Maybe IndexState
$sel:state:UpdateIndexTypeResponse' :: UpdateIndexTypeResponse -> Maybe IndexState
state} -> Maybe IndexState
state) (\s :: UpdateIndexTypeResponse
s@UpdateIndexTypeResponse' {} Maybe IndexState
a -> UpdateIndexTypeResponse
s {$sel:state:UpdateIndexTypeResponse' :: Maybe IndexState
state = Maybe IndexState
a} :: UpdateIndexTypeResponse)

-- | Specifies the type of the specified index after the operation completes.
updateIndexTypeResponse_type :: Lens.Lens' UpdateIndexTypeResponse (Prelude.Maybe IndexType)
updateIndexTypeResponse_type :: Lens' UpdateIndexTypeResponse (Maybe IndexType)
updateIndexTypeResponse_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateIndexTypeResponse' {Maybe IndexType
type' :: Maybe IndexType
$sel:type':UpdateIndexTypeResponse' :: UpdateIndexTypeResponse -> Maybe IndexType
type'} -> Maybe IndexType
type') (\s :: UpdateIndexTypeResponse
s@UpdateIndexTypeResponse' {} Maybe IndexType
a -> UpdateIndexTypeResponse
s {$sel:type':UpdateIndexTypeResponse' :: Maybe IndexType
type' = Maybe IndexType
a} :: UpdateIndexTypeResponse)

-- | The response's http status code.
updateIndexTypeResponse_httpStatus :: Lens.Lens' UpdateIndexTypeResponse Prelude.Int
updateIndexTypeResponse_httpStatus :: Lens' UpdateIndexTypeResponse Int
updateIndexTypeResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateIndexTypeResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateIndexTypeResponse' :: UpdateIndexTypeResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdateIndexTypeResponse
s@UpdateIndexTypeResponse' {} Int
a -> UpdateIndexTypeResponse
s {$sel:httpStatus:UpdateIndexTypeResponse' :: Int
httpStatus = Int
a} :: UpdateIndexTypeResponse)

instance Prelude.NFData UpdateIndexTypeResponse where
  rnf :: UpdateIndexTypeResponse -> ()
rnf UpdateIndexTypeResponse' {Int
Maybe Text
Maybe ISO8601
Maybe IndexState
Maybe IndexType
httpStatus :: Int
type' :: Maybe IndexType
state :: Maybe IndexState
lastUpdatedAt :: Maybe ISO8601
arn :: Maybe Text
$sel:httpStatus:UpdateIndexTypeResponse' :: UpdateIndexTypeResponse -> Int
$sel:type':UpdateIndexTypeResponse' :: UpdateIndexTypeResponse -> Maybe IndexType
$sel:state:UpdateIndexTypeResponse' :: UpdateIndexTypeResponse -> Maybe IndexState
$sel:lastUpdatedAt:UpdateIndexTypeResponse' :: UpdateIndexTypeResponse -> Maybe ISO8601
$sel:arn:UpdateIndexTypeResponse' :: UpdateIndexTypeResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
lastUpdatedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe IndexState
state
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe IndexType
type'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus