{-# 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.UpdateThesaurus
-- 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 a thesaurus for an index.
module Amazonka.Kendra.UpdateThesaurus
  ( -- * Creating a Request
    UpdateThesaurus (..),
    newUpdateThesaurus,

    -- * Request Lenses
    updateThesaurus_description,
    updateThesaurus_name,
    updateThesaurus_roleArn,
    updateThesaurus_sourceS3Path,
    updateThesaurus_id,
    updateThesaurus_indexId,

    -- * Destructuring the Response
    UpdateThesaurusResponse (..),
    newUpdateThesaurusResponse,
  )
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:/ 'newUpdateThesaurus' smart constructor.
data UpdateThesaurus = UpdateThesaurus'
  { -- | A new description for the thesaurus.
    UpdateThesaurus -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | A new name for the thesaurus.
    UpdateThesaurus -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | An IAM role that gives Amazon Kendra permissions to access thesaurus
    -- file specified in @SourceS3Path@.
    UpdateThesaurus -> Maybe Text
roleArn :: Prelude.Maybe Prelude.Text,
    UpdateThesaurus -> Maybe S3Path
sourceS3Path :: Prelude.Maybe S3Path,
    -- | The identifier of the thesaurus you want to update.
    UpdateThesaurus -> Text
id :: Prelude.Text,
    -- | The identifier of the index for the thesaurus.
    UpdateThesaurus -> Text
indexId :: Prelude.Text
  }
  deriving (UpdateThesaurus -> UpdateThesaurus -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateThesaurus -> UpdateThesaurus -> Bool
$c/= :: UpdateThesaurus -> UpdateThesaurus -> Bool
== :: UpdateThesaurus -> UpdateThesaurus -> Bool
$c== :: UpdateThesaurus -> UpdateThesaurus -> Bool
Prelude.Eq, ReadPrec [UpdateThesaurus]
ReadPrec UpdateThesaurus
Int -> ReadS UpdateThesaurus
ReadS [UpdateThesaurus]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateThesaurus]
$creadListPrec :: ReadPrec [UpdateThesaurus]
readPrec :: ReadPrec UpdateThesaurus
$creadPrec :: ReadPrec UpdateThesaurus
readList :: ReadS [UpdateThesaurus]
$creadList :: ReadS [UpdateThesaurus]
readsPrec :: Int -> ReadS UpdateThesaurus
$creadsPrec :: Int -> ReadS UpdateThesaurus
Prelude.Read, Int -> UpdateThesaurus -> ShowS
[UpdateThesaurus] -> ShowS
UpdateThesaurus -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateThesaurus] -> ShowS
$cshowList :: [UpdateThesaurus] -> ShowS
show :: UpdateThesaurus -> String
$cshow :: UpdateThesaurus -> String
showsPrec :: Int -> UpdateThesaurus -> ShowS
$cshowsPrec :: Int -> UpdateThesaurus -> ShowS
Prelude.Show, forall x. Rep UpdateThesaurus x -> UpdateThesaurus
forall x. UpdateThesaurus -> Rep UpdateThesaurus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateThesaurus x -> UpdateThesaurus
$cfrom :: forall x. UpdateThesaurus -> Rep UpdateThesaurus x
Prelude.Generic)

-- |
-- Create a value of 'UpdateThesaurus' 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:
--
-- 'description', 'updateThesaurus_description' - A new description for the thesaurus.
--
-- 'name', 'updateThesaurus_name' - A new name for the thesaurus.
--
-- 'roleArn', 'updateThesaurus_roleArn' - An IAM role that gives Amazon Kendra permissions to access thesaurus
-- file specified in @SourceS3Path@.
--
-- 'sourceS3Path', 'updateThesaurus_sourceS3Path' - Undocumented member.
--
-- 'id', 'updateThesaurus_id' - The identifier of the thesaurus you want to update.
--
-- 'indexId', 'updateThesaurus_indexId' - The identifier of the index for the thesaurus.
newUpdateThesaurus ::
  -- | 'id'
  Prelude.Text ->
  -- | 'indexId'
  Prelude.Text ->
  UpdateThesaurus
newUpdateThesaurus :: Text -> Text -> UpdateThesaurus
newUpdateThesaurus Text
pId_ Text
pIndexId_ =
  UpdateThesaurus'
    { $sel:description:UpdateThesaurus' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:name:UpdateThesaurus' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:roleArn:UpdateThesaurus' :: Maybe Text
roleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceS3Path:UpdateThesaurus' :: Maybe S3Path
sourceS3Path = forall a. Maybe a
Prelude.Nothing,
      $sel:id:UpdateThesaurus' :: Text
id = Text
pId_,
      $sel:indexId:UpdateThesaurus' :: Text
indexId = Text
pIndexId_
    }

-- | A new description for the thesaurus.
updateThesaurus_description :: Lens.Lens' UpdateThesaurus (Prelude.Maybe Prelude.Text)
updateThesaurus_description :: Lens' UpdateThesaurus (Maybe Text)
updateThesaurus_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateThesaurus' {Maybe Text
description :: Maybe Text
$sel:description:UpdateThesaurus' :: UpdateThesaurus -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateThesaurus
s@UpdateThesaurus' {} Maybe Text
a -> UpdateThesaurus
s {$sel:description:UpdateThesaurus' :: Maybe Text
description = Maybe Text
a} :: UpdateThesaurus)

-- | A new name for the thesaurus.
updateThesaurus_name :: Lens.Lens' UpdateThesaurus (Prelude.Maybe Prelude.Text)
updateThesaurus_name :: Lens' UpdateThesaurus (Maybe Text)
updateThesaurus_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateThesaurus' {Maybe Text
name :: Maybe Text
$sel:name:UpdateThesaurus' :: UpdateThesaurus -> Maybe Text
name} -> Maybe Text
name) (\s :: UpdateThesaurus
s@UpdateThesaurus' {} Maybe Text
a -> UpdateThesaurus
s {$sel:name:UpdateThesaurus' :: Maybe Text
name = Maybe Text
a} :: UpdateThesaurus)

-- | An IAM role that gives Amazon Kendra permissions to access thesaurus
-- file specified in @SourceS3Path@.
updateThesaurus_roleArn :: Lens.Lens' UpdateThesaurus (Prelude.Maybe Prelude.Text)
updateThesaurus_roleArn :: Lens' UpdateThesaurus (Maybe Text)
updateThesaurus_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateThesaurus' {Maybe Text
roleArn :: Maybe Text
$sel:roleArn:UpdateThesaurus' :: UpdateThesaurus -> Maybe Text
roleArn} -> Maybe Text
roleArn) (\s :: UpdateThesaurus
s@UpdateThesaurus' {} Maybe Text
a -> UpdateThesaurus
s {$sel:roleArn:UpdateThesaurus' :: Maybe Text
roleArn = Maybe Text
a} :: UpdateThesaurus)

-- | Undocumented member.
updateThesaurus_sourceS3Path :: Lens.Lens' UpdateThesaurus (Prelude.Maybe S3Path)
updateThesaurus_sourceS3Path :: Lens' UpdateThesaurus (Maybe S3Path)
updateThesaurus_sourceS3Path = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateThesaurus' {Maybe S3Path
sourceS3Path :: Maybe S3Path
$sel:sourceS3Path:UpdateThesaurus' :: UpdateThesaurus -> Maybe S3Path
sourceS3Path} -> Maybe S3Path
sourceS3Path) (\s :: UpdateThesaurus
s@UpdateThesaurus' {} Maybe S3Path
a -> UpdateThesaurus
s {$sel:sourceS3Path:UpdateThesaurus' :: Maybe S3Path
sourceS3Path = Maybe S3Path
a} :: UpdateThesaurus)

-- | The identifier of the thesaurus you want to update.
updateThesaurus_id :: Lens.Lens' UpdateThesaurus Prelude.Text
updateThesaurus_id :: Lens' UpdateThesaurus Text
updateThesaurus_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateThesaurus' {Text
id :: Text
$sel:id:UpdateThesaurus' :: UpdateThesaurus -> Text
id} -> Text
id) (\s :: UpdateThesaurus
s@UpdateThesaurus' {} Text
a -> UpdateThesaurus
s {$sel:id:UpdateThesaurus' :: Text
id = Text
a} :: UpdateThesaurus)

-- | The identifier of the index for the thesaurus.
updateThesaurus_indexId :: Lens.Lens' UpdateThesaurus Prelude.Text
updateThesaurus_indexId :: Lens' UpdateThesaurus Text
updateThesaurus_indexId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateThesaurus' {Text
indexId :: Text
$sel:indexId:UpdateThesaurus' :: UpdateThesaurus -> Text
indexId} -> Text
indexId) (\s :: UpdateThesaurus
s@UpdateThesaurus' {} Text
a -> UpdateThesaurus
s {$sel:indexId:UpdateThesaurus' :: Text
indexId = Text
a} :: UpdateThesaurus)

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

instance Prelude.Hashable UpdateThesaurus where
  hashWithSalt :: Int -> UpdateThesaurus -> Int
hashWithSalt Int
_salt UpdateThesaurus' {Maybe Text
Maybe S3Path
Text
indexId :: Text
id :: Text
sourceS3Path :: Maybe S3Path
roleArn :: Maybe Text
name :: Maybe Text
description :: Maybe Text
$sel:indexId:UpdateThesaurus' :: UpdateThesaurus -> Text
$sel:id:UpdateThesaurus' :: UpdateThesaurus -> Text
$sel:sourceS3Path:UpdateThesaurus' :: UpdateThesaurus -> Maybe S3Path
$sel:roleArn:UpdateThesaurus' :: UpdateThesaurus -> Maybe Text
$sel:name:UpdateThesaurus' :: UpdateThesaurus -> Maybe Text
$sel:description:UpdateThesaurus' :: UpdateThesaurus -> Maybe Text
..} =
    Int
_salt
      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` Maybe S3Path
sourceS3Path
      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 UpdateThesaurus where
  rnf :: UpdateThesaurus -> ()
rnf UpdateThesaurus' {Maybe Text
Maybe S3Path
Text
indexId :: Text
id :: Text
sourceS3Path :: Maybe S3Path
roleArn :: Maybe Text
name :: Maybe Text
description :: Maybe Text
$sel:indexId:UpdateThesaurus' :: UpdateThesaurus -> Text
$sel:id:UpdateThesaurus' :: UpdateThesaurus -> Text
$sel:sourceS3Path:UpdateThesaurus' :: UpdateThesaurus -> Maybe S3Path
$sel:roleArn:UpdateThesaurus' :: UpdateThesaurus -> Maybe Text
$sel:name:UpdateThesaurus' :: UpdateThesaurus -> Maybe Text
$sel:description:UpdateThesaurus' :: UpdateThesaurus -> Maybe Text
..} =
    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 Maybe S3Path
sourceS3Path
      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 UpdateThesaurus where
  toHeaders :: UpdateThesaurus -> [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.UpdateThesaurus" ::
                          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 UpdateThesaurus where
  toJSON :: UpdateThesaurus -> Value
toJSON UpdateThesaurus' {Maybe Text
Maybe S3Path
Text
indexId :: Text
id :: Text
sourceS3Path :: Maybe S3Path
roleArn :: Maybe Text
name :: Maybe Text
description :: Maybe Text
$sel:indexId:UpdateThesaurus' :: UpdateThesaurus -> Text
$sel:id:UpdateThesaurus' :: UpdateThesaurus -> Text
$sel:sourceS3Path:UpdateThesaurus' :: UpdateThesaurus -> Maybe S3Path
$sel:roleArn:UpdateThesaurus' :: UpdateThesaurus -> Maybe Text
$sel:name:UpdateThesaurus' :: UpdateThesaurus -> Maybe Text
$sel:description:UpdateThesaurus' :: UpdateThesaurus -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (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,
            (Key
"SourceS3Path" 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 S3Path
sourceS3Path,
            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 UpdateThesaurus where
  toPath :: UpdateThesaurus -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

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

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