{-# 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.Kendra.UpdateExperience
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates your Amazon Kendra experience such as a search application. For
-- more information on creating a search application experience, see
-- <https://docs.aws.amazon.com/kendra/latest/dg/deploying-search-experience-no-code.html Building a search experience with no code>.
module Amazonka.Kendra.UpdateExperience
  ( -- * Creating a Request
    UpdateExperience (..),
    newUpdateExperience,

    -- * Request Lenses
    updateExperience_configuration,
    updateExperience_description,
    updateExperience_name,
    updateExperience_roleArn,
    updateExperience_id,
    updateExperience_indexId,

    -- * Destructuring the Response
    UpdateExperienceResponse (..),
    newUpdateExperienceResponse,
  )
where

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

-- | /See:/ 'newUpdateExperience' smart constructor.
data UpdateExperience = UpdateExperience'
  { -- | Configuration information you want to update for your Amazon Kendra
    -- experience.
    UpdateExperience -> Maybe ExperienceConfiguration
configuration :: Prelude.Maybe ExperienceConfiguration,
    -- | A new description for your Amazon Kendra experience.
    UpdateExperience -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | A new name for your Amazon Kendra experience.
    UpdateExperience -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of a role with permission to access
    -- @Query@ API, @QuerySuggestions@ API, @SubmitFeedback@ API, and IAM
    -- Identity Center that stores your user and group information. For more
    -- information, see
    -- <https://docs.aws.amazon.com/kendra/latest/dg/iam-roles.html IAM roles for Amazon Kendra>.
    UpdateExperience -> Maybe Text
roleArn :: Prelude.Maybe Prelude.Text,
    -- | The identifier of your Amazon Kendra experience you want to update.
    UpdateExperience -> Text
id :: Prelude.Text,
    -- | The identifier of the index for your Amazon Kendra experience.
    UpdateExperience -> Text
indexId :: Prelude.Text
  }
  deriving (UpdateExperience -> UpdateExperience -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateExperience -> UpdateExperience -> Bool
$c/= :: UpdateExperience -> UpdateExperience -> Bool
== :: UpdateExperience -> UpdateExperience -> Bool
$c== :: UpdateExperience -> UpdateExperience -> Bool
Prelude.Eq, ReadPrec [UpdateExperience]
ReadPrec UpdateExperience
Int -> ReadS UpdateExperience
ReadS [UpdateExperience]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateExperience]
$creadListPrec :: ReadPrec [UpdateExperience]
readPrec :: ReadPrec UpdateExperience
$creadPrec :: ReadPrec UpdateExperience
readList :: ReadS [UpdateExperience]
$creadList :: ReadS [UpdateExperience]
readsPrec :: Int -> ReadS UpdateExperience
$creadsPrec :: Int -> ReadS UpdateExperience
Prelude.Read, Int -> UpdateExperience -> ShowS
[UpdateExperience] -> ShowS
UpdateExperience -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateExperience] -> ShowS
$cshowList :: [UpdateExperience] -> ShowS
show :: UpdateExperience -> String
$cshow :: UpdateExperience -> String
showsPrec :: Int -> UpdateExperience -> ShowS
$cshowsPrec :: Int -> UpdateExperience -> ShowS
Prelude.Show, forall x. Rep UpdateExperience x -> UpdateExperience
forall x. UpdateExperience -> Rep UpdateExperience x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateExperience x -> UpdateExperience
$cfrom :: forall x. UpdateExperience -> Rep UpdateExperience x
Prelude.Generic)

-- |
-- Create a value of 'UpdateExperience' 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:
--
-- 'configuration', 'updateExperience_configuration' - Configuration information you want to update for your Amazon Kendra
-- experience.
--
-- 'description', 'updateExperience_description' - A new description for your Amazon Kendra experience.
--
-- 'name', 'updateExperience_name' - A new name for your Amazon Kendra experience.
--
-- 'roleArn', 'updateExperience_roleArn' - The Amazon Resource Name (ARN) of a role with permission to access
-- @Query@ API, @QuerySuggestions@ API, @SubmitFeedback@ API, and IAM
-- Identity Center that stores your user and group information. For more
-- information, see
-- <https://docs.aws.amazon.com/kendra/latest/dg/iam-roles.html IAM roles for Amazon Kendra>.
--
-- 'id', 'updateExperience_id' - The identifier of your Amazon Kendra experience you want to update.
--
-- 'indexId', 'updateExperience_indexId' - The identifier of the index for your Amazon Kendra experience.
newUpdateExperience ::
  -- | 'id'
  Prelude.Text ->
  -- | 'indexId'
  Prelude.Text ->
  UpdateExperience
newUpdateExperience :: Text -> Text -> UpdateExperience
newUpdateExperience Text
pId_ Text
pIndexId_ =
  UpdateExperience'
    { $sel:configuration:UpdateExperience' :: Maybe ExperienceConfiguration
configuration = forall a. Maybe a
Prelude.Nothing,
      $sel:description:UpdateExperience' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:name:UpdateExperience' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:roleArn:UpdateExperience' :: Maybe Text
roleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:id:UpdateExperience' :: Text
id = Text
pId_,
      $sel:indexId:UpdateExperience' :: Text
indexId = Text
pIndexId_
    }

-- | Configuration information you want to update for your Amazon Kendra
-- experience.
updateExperience_configuration :: Lens.Lens' UpdateExperience (Prelude.Maybe ExperienceConfiguration)
updateExperience_configuration :: Lens' UpdateExperience (Maybe ExperienceConfiguration)
updateExperience_configuration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateExperience' {Maybe ExperienceConfiguration
configuration :: Maybe ExperienceConfiguration
$sel:configuration:UpdateExperience' :: UpdateExperience -> Maybe ExperienceConfiguration
configuration} -> Maybe ExperienceConfiguration
configuration) (\s :: UpdateExperience
s@UpdateExperience' {} Maybe ExperienceConfiguration
a -> UpdateExperience
s {$sel:configuration:UpdateExperience' :: Maybe ExperienceConfiguration
configuration = Maybe ExperienceConfiguration
a} :: UpdateExperience)

-- | A new description for your Amazon Kendra experience.
updateExperience_description :: Lens.Lens' UpdateExperience (Prelude.Maybe Prelude.Text)
updateExperience_description :: Lens' UpdateExperience (Maybe Text)
updateExperience_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateExperience' {Maybe Text
description :: Maybe Text
$sel:description:UpdateExperience' :: UpdateExperience -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateExperience
s@UpdateExperience' {} Maybe Text
a -> UpdateExperience
s {$sel:description:UpdateExperience' :: Maybe Text
description = Maybe Text
a} :: UpdateExperience)

-- | A new name for your Amazon Kendra experience.
updateExperience_name :: Lens.Lens' UpdateExperience (Prelude.Maybe Prelude.Text)
updateExperience_name :: Lens' UpdateExperience (Maybe Text)
updateExperience_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateExperience' {Maybe Text
name :: Maybe Text
$sel:name:UpdateExperience' :: UpdateExperience -> Maybe Text
name} -> Maybe Text
name) (\s :: UpdateExperience
s@UpdateExperience' {} Maybe Text
a -> UpdateExperience
s {$sel:name:UpdateExperience' :: Maybe Text
name = Maybe Text
a} :: UpdateExperience)

-- | The Amazon Resource Name (ARN) of a role with permission to access
-- @Query@ API, @QuerySuggestions@ API, @SubmitFeedback@ API, and IAM
-- Identity Center that stores your user and group information. For more
-- information, see
-- <https://docs.aws.amazon.com/kendra/latest/dg/iam-roles.html IAM roles for Amazon Kendra>.
updateExperience_roleArn :: Lens.Lens' UpdateExperience (Prelude.Maybe Prelude.Text)
updateExperience_roleArn :: Lens' UpdateExperience (Maybe Text)
updateExperience_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateExperience' {Maybe Text
roleArn :: Maybe Text
$sel:roleArn:UpdateExperience' :: UpdateExperience -> Maybe Text
roleArn} -> Maybe Text
roleArn) (\s :: UpdateExperience
s@UpdateExperience' {} Maybe Text
a -> UpdateExperience
s {$sel:roleArn:UpdateExperience' :: Maybe Text
roleArn = Maybe Text
a} :: UpdateExperience)

-- | The identifier of your Amazon Kendra experience you want to update.
updateExperience_id :: Lens.Lens' UpdateExperience Prelude.Text
updateExperience_id :: Lens' UpdateExperience Text
updateExperience_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateExperience' {Text
id :: Text
$sel:id:UpdateExperience' :: UpdateExperience -> Text
id} -> Text
id) (\s :: UpdateExperience
s@UpdateExperience' {} Text
a -> UpdateExperience
s {$sel:id:UpdateExperience' :: Text
id = Text
a} :: UpdateExperience)

-- | The identifier of the index for your Amazon Kendra experience.
updateExperience_indexId :: Lens.Lens' UpdateExperience Prelude.Text
updateExperience_indexId :: Lens' UpdateExperience Text
updateExperience_indexId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateExperience' {Text
indexId :: Text
$sel:indexId:UpdateExperience' :: UpdateExperience -> Text
indexId} -> Text
indexId) (\s :: UpdateExperience
s@UpdateExperience' {} Text
a -> UpdateExperience
s {$sel:indexId:UpdateExperience' :: Text
indexId = Text
a} :: UpdateExperience)

instance Core.AWSRequest UpdateExperience where
  type
    AWSResponse UpdateExperience =
      UpdateExperienceResponse
  request :: (Service -> Service)
-> UpdateExperience -> Request UpdateExperience
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 UpdateExperience
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateExperience)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull UpdateExperienceResponse
UpdateExperienceResponse'

instance Prelude.Hashable UpdateExperience where
  hashWithSalt :: Int -> UpdateExperience -> Int
hashWithSalt Int
_salt UpdateExperience' {Maybe Text
Maybe ExperienceConfiguration
Text
indexId :: Text
id :: Text
roleArn :: Maybe Text
name :: Maybe Text
description :: Maybe Text
configuration :: Maybe ExperienceConfiguration
$sel:indexId:UpdateExperience' :: UpdateExperience -> Text
$sel:id:UpdateExperience' :: UpdateExperience -> Text
$sel:roleArn:UpdateExperience' :: UpdateExperience -> Maybe Text
$sel:name:UpdateExperience' :: UpdateExperience -> Maybe Text
$sel:description:UpdateExperience' :: UpdateExperience -> Maybe Text
$sel:configuration:UpdateExperience' :: UpdateExperience -> Maybe ExperienceConfiguration
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ExperienceConfiguration
configuration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
roleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
indexId

instance Prelude.NFData UpdateExperience where
  rnf :: UpdateExperience -> ()
rnf UpdateExperience' {Maybe Text
Maybe ExperienceConfiguration
Text
indexId :: Text
id :: Text
roleArn :: Maybe Text
name :: Maybe Text
description :: Maybe Text
configuration :: Maybe ExperienceConfiguration
$sel:indexId:UpdateExperience' :: UpdateExperience -> Text
$sel:id:UpdateExperience' :: UpdateExperience -> Text
$sel:roleArn:UpdateExperience' :: UpdateExperience -> Maybe Text
$sel:name:UpdateExperience' :: UpdateExperience -> Maybe Text
$sel:description:UpdateExperience' :: UpdateExperience -> Maybe Text
$sel:configuration:UpdateExperience' :: UpdateExperience -> Maybe ExperienceConfiguration
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ExperienceConfiguration
configuration
      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 Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
roleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
indexId

instance Data.ToHeaders UpdateExperience where
  toHeaders :: UpdateExperience -> [Header]
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 -> [Header]
Data.=# ( ByteString
"AWSKendraFrontendService.UpdateExperience" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateExperience where
  toJSON :: UpdateExperience -> Value
toJSON UpdateExperience' {Maybe Text
Maybe ExperienceConfiguration
Text
indexId :: Text
id :: Text
roleArn :: Maybe Text
name :: Maybe Text
description :: Maybe Text
configuration :: Maybe ExperienceConfiguration
$sel:indexId:UpdateExperience' :: UpdateExperience -> Text
$sel:id:UpdateExperience' :: UpdateExperience -> Text
$sel:roleArn:UpdateExperience' :: UpdateExperience -> Maybe Text
$sel:name:UpdateExperience' :: UpdateExperience -> Maybe Text
$sel:description:UpdateExperience' :: UpdateExperience -> Maybe Text
$sel:configuration:UpdateExperience' :: UpdateExperience -> Maybe ExperienceConfiguration
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Configuration" 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 ExperienceConfiguration
configuration,
            (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
"Name" 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
name,
            (Key
"RoleArn" 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
roleArn,
            forall a. a -> Maybe a
Prelude.Just (Key
"Id" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
id),
            forall a. a -> Maybe a
Prelude.Just (Key
"IndexId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
indexId)
          ]
      )

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

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

-- | /See:/ 'newUpdateExperienceResponse' smart constructor.
data UpdateExperienceResponse = UpdateExperienceResponse'
  {
  }
  deriving (UpdateExperienceResponse -> UpdateExperienceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateExperienceResponse -> UpdateExperienceResponse -> Bool
$c/= :: UpdateExperienceResponse -> UpdateExperienceResponse -> Bool
== :: UpdateExperienceResponse -> UpdateExperienceResponse -> Bool
$c== :: UpdateExperienceResponse -> UpdateExperienceResponse -> Bool
Prelude.Eq, ReadPrec [UpdateExperienceResponse]
ReadPrec UpdateExperienceResponse
Int -> ReadS UpdateExperienceResponse
ReadS [UpdateExperienceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateExperienceResponse]
$creadListPrec :: ReadPrec [UpdateExperienceResponse]
readPrec :: ReadPrec UpdateExperienceResponse
$creadPrec :: ReadPrec UpdateExperienceResponse
readList :: ReadS [UpdateExperienceResponse]
$creadList :: ReadS [UpdateExperienceResponse]
readsPrec :: Int -> ReadS UpdateExperienceResponse
$creadsPrec :: Int -> ReadS UpdateExperienceResponse
Prelude.Read, Int -> UpdateExperienceResponse -> ShowS
[UpdateExperienceResponse] -> ShowS
UpdateExperienceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateExperienceResponse] -> ShowS
$cshowList :: [UpdateExperienceResponse] -> ShowS
show :: UpdateExperienceResponse -> String
$cshow :: UpdateExperienceResponse -> String
showsPrec :: Int -> UpdateExperienceResponse -> ShowS
$cshowsPrec :: Int -> UpdateExperienceResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateExperienceResponse x -> UpdateExperienceResponse
forall x.
UpdateExperienceResponse -> Rep UpdateExperienceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateExperienceResponse x -> UpdateExperienceResponse
$cfrom :: forall x.
UpdateExperienceResponse -> Rep UpdateExperienceResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateExperienceResponse' 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.
newUpdateExperienceResponse ::
  UpdateExperienceResponse
newUpdateExperienceResponse :: UpdateExperienceResponse
newUpdateExperienceResponse =
  UpdateExperienceResponse
UpdateExperienceResponse'

instance Prelude.NFData UpdateExperienceResponse where
  rnf :: UpdateExperienceResponse -> ()
rnf UpdateExperienceResponse
_ = ()