{-# 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.CreateFaq
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates an new set of frequently asked question (FAQ) questions and
-- answers.
--
-- Adding FAQs to an index is an asynchronous operation.
--
-- For an example of adding an FAQ to an index using Python and Java SDKs,
-- see
-- <https://docs.aws.amazon.com/kendra/latest/dg/in-creating-faq.html#using-faq-file Using your FAQ file>.
module Amazonka.Kendra.CreateFaq
  ( -- * Creating a Request
    CreateFaq (..),
    newCreateFaq,

    -- * Request Lenses
    createFaq_clientToken,
    createFaq_description,
    createFaq_fileFormat,
    createFaq_languageCode,
    createFaq_tags,
    createFaq_indexId,
    createFaq_name,
    createFaq_s3Path,
    createFaq_roleArn,

    -- * Destructuring the Response
    CreateFaqResponse (..),
    newCreateFaqResponse,

    -- * Response Lenses
    createFaqResponse_id,
    createFaqResponse_httpStatus,
  )
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:/ 'newCreateFaq' smart constructor.
data CreateFaq = CreateFaq'
  { -- | A token that you provide to identify the request to create a FAQ.
    -- Multiple calls to the @CreateFaqRequest@ API with the same client token
    -- will create only one FAQ.
    CreateFaq -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | A description for the FAQ.
    CreateFaq -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The format of the FAQ input file. You can choose between a basic CSV
    -- format, a CSV format that includes customs attributes in a header, and a
    -- JSON format that includes custom attributes.
    --
    -- The format must match the format of the file stored in the S3 bucket
    -- identified in the @S3Path@ parameter.
    --
    -- For more information, see
    -- <https://docs.aws.amazon.com/kendra/latest/dg/in-creating-faq.html Adding questions and answers>.
    CreateFaq -> Maybe FaqFileFormat
fileFormat :: Prelude.Maybe FaqFileFormat,
    -- | The code for a language. This allows you to support a language for the
    -- FAQ document. English is supported by default. For more information on
    -- supported languages, including their codes, see
    -- <https://docs.aws.amazon.com/kendra/latest/dg/in-adding-languages.html Adding documents in languages other than English>.
    CreateFaq -> Maybe Text
languageCode :: Prelude.Maybe Prelude.Text,
    -- | A list of key-value pairs that identify the FAQ. You can use the tags to
    -- identify and organize your resources and to control access to resources.
    CreateFaq -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The identifier of the index for the FAQ.
    CreateFaq -> Text
indexId :: Prelude.Text,
    -- | A name for the FAQ.
    CreateFaq -> Text
name :: Prelude.Text,
    -- | The path to the FAQ file in S3.
    CreateFaq -> S3Path
s3Path :: S3Path,
    -- | The Amazon Resource Name (ARN) of a role with permission to access the
    -- S3 bucket that contains the FAQs. For more information, see
    -- <https://docs.aws.amazon.com/kendra/latest/dg/iam-roles.html IAM Roles for Amazon Kendra>.
    CreateFaq -> Text
roleArn :: Prelude.Text
  }
  deriving (CreateFaq -> CreateFaq -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateFaq -> CreateFaq -> Bool
$c/= :: CreateFaq -> CreateFaq -> Bool
== :: CreateFaq -> CreateFaq -> Bool
$c== :: CreateFaq -> CreateFaq -> Bool
Prelude.Eq, ReadPrec [CreateFaq]
ReadPrec CreateFaq
Int -> ReadS CreateFaq
ReadS [CreateFaq]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateFaq]
$creadListPrec :: ReadPrec [CreateFaq]
readPrec :: ReadPrec CreateFaq
$creadPrec :: ReadPrec CreateFaq
readList :: ReadS [CreateFaq]
$creadList :: ReadS [CreateFaq]
readsPrec :: Int -> ReadS CreateFaq
$creadsPrec :: Int -> ReadS CreateFaq
Prelude.Read, Int -> CreateFaq -> ShowS
[CreateFaq] -> ShowS
CreateFaq -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateFaq] -> ShowS
$cshowList :: [CreateFaq] -> ShowS
show :: CreateFaq -> String
$cshow :: CreateFaq -> String
showsPrec :: Int -> CreateFaq -> ShowS
$cshowsPrec :: Int -> CreateFaq -> ShowS
Prelude.Show, forall x. Rep CreateFaq x -> CreateFaq
forall x. CreateFaq -> Rep CreateFaq x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateFaq x -> CreateFaq
$cfrom :: forall x. CreateFaq -> Rep CreateFaq x
Prelude.Generic)

-- |
-- Create a value of 'CreateFaq' 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:
--
-- 'clientToken', 'createFaq_clientToken' - A token that you provide to identify the request to create a FAQ.
-- Multiple calls to the @CreateFaqRequest@ API with the same client token
-- will create only one FAQ.
--
-- 'description', 'createFaq_description' - A description for the FAQ.
--
-- 'fileFormat', 'createFaq_fileFormat' - The format of the FAQ input file. You can choose between a basic CSV
-- format, a CSV format that includes customs attributes in a header, and a
-- JSON format that includes custom attributes.
--
-- The format must match the format of the file stored in the S3 bucket
-- identified in the @S3Path@ parameter.
--
-- For more information, see
-- <https://docs.aws.amazon.com/kendra/latest/dg/in-creating-faq.html Adding questions and answers>.
--
-- 'languageCode', 'createFaq_languageCode' - The code for a language. This allows you to support a language for the
-- FAQ document. English is supported by default. For more information on
-- supported languages, including their codes, see
-- <https://docs.aws.amazon.com/kendra/latest/dg/in-adding-languages.html Adding documents in languages other than English>.
--
-- 'tags', 'createFaq_tags' - A list of key-value pairs that identify the FAQ. You can use the tags to
-- identify and organize your resources and to control access to resources.
--
-- 'indexId', 'createFaq_indexId' - The identifier of the index for the FAQ.
--
-- 'name', 'createFaq_name' - A name for the FAQ.
--
-- 's3Path', 'createFaq_s3Path' - The path to the FAQ file in S3.
--
-- 'roleArn', 'createFaq_roleArn' - The Amazon Resource Name (ARN) of a role with permission to access the
-- S3 bucket that contains the FAQs. For more information, see
-- <https://docs.aws.amazon.com/kendra/latest/dg/iam-roles.html IAM Roles for Amazon Kendra>.
newCreateFaq ::
  -- | 'indexId'
  Prelude.Text ->
  -- | 'name'
  Prelude.Text ->
  -- | 's3Path'
  S3Path ->
  -- | 'roleArn'
  Prelude.Text ->
  CreateFaq
newCreateFaq :: Text -> Text -> S3Path -> Text -> CreateFaq
newCreateFaq Text
pIndexId_ Text
pName_ S3Path
pS3Path_ Text
pRoleArn_ =
  CreateFaq'
    { $sel:clientToken:CreateFaq' :: Maybe Text
clientToken = forall a. Maybe a
Prelude.Nothing,
      $sel:description:CreateFaq' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:fileFormat:CreateFaq' :: Maybe FaqFileFormat
fileFormat = forall a. Maybe a
Prelude.Nothing,
      $sel:languageCode:CreateFaq' :: Maybe Text
languageCode = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateFaq' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:indexId:CreateFaq' :: Text
indexId = Text
pIndexId_,
      $sel:name:CreateFaq' :: Text
name = Text
pName_,
      $sel:s3Path:CreateFaq' :: S3Path
s3Path = S3Path
pS3Path_,
      $sel:roleArn:CreateFaq' :: Text
roleArn = Text
pRoleArn_
    }

-- | A token that you provide to identify the request to create a FAQ.
-- Multiple calls to the @CreateFaqRequest@ API with the same client token
-- will create only one FAQ.
createFaq_clientToken :: Lens.Lens' CreateFaq (Prelude.Maybe Prelude.Text)
createFaq_clientToken :: Lens' CreateFaq (Maybe Text)
createFaq_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFaq' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:CreateFaq' :: CreateFaq -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: CreateFaq
s@CreateFaq' {} Maybe Text
a -> CreateFaq
s {$sel:clientToken:CreateFaq' :: Maybe Text
clientToken = Maybe Text
a} :: CreateFaq)

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

-- | The format of the FAQ input file. You can choose between a basic CSV
-- format, a CSV format that includes customs attributes in a header, and a
-- JSON format that includes custom attributes.
--
-- The format must match the format of the file stored in the S3 bucket
-- identified in the @S3Path@ parameter.
--
-- For more information, see
-- <https://docs.aws.amazon.com/kendra/latest/dg/in-creating-faq.html Adding questions and answers>.
createFaq_fileFormat :: Lens.Lens' CreateFaq (Prelude.Maybe FaqFileFormat)
createFaq_fileFormat :: Lens' CreateFaq (Maybe FaqFileFormat)
createFaq_fileFormat = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFaq' {Maybe FaqFileFormat
fileFormat :: Maybe FaqFileFormat
$sel:fileFormat:CreateFaq' :: CreateFaq -> Maybe FaqFileFormat
fileFormat} -> Maybe FaqFileFormat
fileFormat) (\s :: CreateFaq
s@CreateFaq' {} Maybe FaqFileFormat
a -> CreateFaq
s {$sel:fileFormat:CreateFaq' :: Maybe FaqFileFormat
fileFormat = Maybe FaqFileFormat
a} :: CreateFaq)

-- | The code for a language. This allows you to support a language for the
-- FAQ document. English is supported by default. For more information on
-- supported languages, including their codes, see
-- <https://docs.aws.amazon.com/kendra/latest/dg/in-adding-languages.html Adding documents in languages other than English>.
createFaq_languageCode :: Lens.Lens' CreateFaq (Prelude.Maybe Prelude.Text)
createFaq_languageCode :: Lens' CreateFaq (Maybe Text)
createFaq_languageCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFaq' {Maybe Text
languageCode :: Maybe Text
$sel:languageCode:CreateFaq' :: CreateFaq -> Maybe Text
languageCode} -> Maybe Text
languageCode) (\s :: CreateFaq
s@CreateFaq' {} Maybe Text
a -> CreateFaq
s {$sel:languageCode:CreateFaq' :: Maybe Text
languageCode = Maybe Text
a} :: CreateFaq)

-- | A list of key-value pairs that identify the FAQ. You can use the tags to
-- identify and organize your resources and to control access to resources.
createFaq_tags :: Lens.Lens' CreateFaq (Prelude.Maybe [Tag])
createFaq_tags :: Lens' CreateFaq (Maybe [Tag])
createFaq_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFaq' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateFaq' :: CreateFaq -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateFaq
s@CreateFaq' {} Maybe [Tag]
a -> CreateFaq
s {$sel:tags:CreateFaq' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateFaq) 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

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

-- | A name for the FAQ.
createFaq_name :: Lens.Lens' CreateFaq Prelude.Text
createFaq_name :: Lens' CreateFaq Text
createFaq_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFaq' {Text
name :: Text
$sel:name:CreateFaq' :: CreateFaq -> Text
name} -> Text
name) (\s :: CreateFaq
s@CreateFaq' {} Text
a -> CreateFaq
s {$sel:name:CreateFaq' :: Text
name = Text
a} :: CreateFaq)

-- | The path to the FAQ file in S3.
createFaq_s3Path :: Lens.Lens' CreateFaq S3Path
createFaq_s3Path :: Lens' CreateFaq S3Path
createFaq_s3Path = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFaq' {S3Path
s3Path :: S3Path
$sel:s3Path:CreateFaq' :: CreateFaq -> S3Path
s3Path} -> S3Path
s3Path) (\s :: CreateFaq
s@CreateFaq' {} S3Path
a -> CreateFaq
s {$sel:s3Path:CreateFaq' :: S3Path
s3Path = S3Path
a} :: CreateFaq)

-- | The Amazon Resource Name (ARN) of a role with permission to access the
-- S3 bucket that contains the FAQs. For more information, see
-- <https://docs.aws.amazon.com/kendra/latest/dg/iam-roles.html IAM Roles for Amazon Kendra>.
createFaq_roleArn :: Lens.Lens' CreateFaq Prelude.Text
createFaq_roleArn :: Lens' CreateFaq Text
createFaq_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFaq' {Text
roleArn :: Text
$sel:roleArn:CreateFaq' :: CreateFaq -> Text
roleArn} -> Text
roleArn) (\s :: CreateFaq
s@CreateFaq' {} Text
a -> CreateFaq
s {$sel:roleArn:CreateFaq' :: Text
roleArn = Text
a} :: CreateFaq)

instance Core.AWSRequest CreateFaq where
  type AWSResponse CreateFaq = CreateFaqResponse
  request :: (Service -> Service) -> CreateFaq -> Request CreateFaq
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 CreateFaq
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateFaq)))
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 -> Int -> CreateFaqResponse
CreateFaqResponse'
            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
"Id")
            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 CreateFaq where
  hashWithSalt :: Int -> CreateFaq -> Int
hashWithSalt Int
_salt CreateFaq' {Maybe [Tag]
Maybe Text
Maybe FaqFileFormat
Text
S3Path
roleArn :: Text
s3Path :: S3Path
name :: Text
indexId :: Text
tags :: Maybe [Tag]
languageCode :: Maybe Text
fileFormat :: Maybe FaqFileFormat
description :: Maybe Text
clientToken :: Maybe Text
$sel:roleArn:CreateFaq' :: CreateFaq -> Text
$sel:s3Path:CreateFaq' :: CreateFaq -> S3Path
$sel:name:CreateFaq' :: CreateFaq -> Text
$sel:indexId:CreateFaq' :: CreateFaq -> Text
$sel:tags:CreateFaq' :: CreateFaq -> Maybe [Tag]
$sel:languageCode:CreateFaq' :: CreateFaq -> Maybe Text
$sel:fileFormat:CreateFaq' :: CreateFaq -> Maybe FaqFileFormat
$sel:description:CreateFaq' :: CreateFaq -> Maybe Text
$sel:clientToken:CreateFaq' :: CreateFaq -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FaqFileFormat
fileFormat
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
languageCode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
indexId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` S3Path
s3Path
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
roleArn

instance Prelude.NFData CreateFaq where
  rnf :: CreateFaq -> ()
rnf CreateFaq' {Maybe [Tag]
Maybe Text
Maybe FaqFileFormat
Text
S3Path
roleArn :: Text
s3Path :: S3Path
name :: Text
indexId :: Text
tags :: Maybe [Tag]
languageCode :: Maybe Text
fileFormat :: Maybe FaqFileFormat
description :: Maybe Text
clientToken :: Maybe Text
$sel:roleArn:CreateFaq' :: CreateFaq -> Text
$sel:s3Path:CreateFaq' :: CreateFaq -> S3Path
$sel:name:CreateFaq' :: CreateFaq -> Text
$sel:indexId:CreateFaq' :: CreateFaq -> Text
$sel:tags:CreateFaq' :: CreateFaq -> Maybe [Tag]
$sel:languageCode:CreateFaq' :: CreateFaq -> Maybe Text
$sel:fileFormat:CreateFaq' :: CreateFaq -> Maybe FaqFileFormat
$sel:description:CreateFaq' :: CreateFaq -> Maybe Text
$sel:clientToken:CreateFaq' :: CreateFaq -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
      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 FaqFileFormat
fileFormat
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
languageCode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
indexId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf S3Path
s3Path
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
roleArn

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

instance Data.ToJSON CreateFaq where
  toJSON :: CreateFaq -> Value
toJSON CreateFaq' {Maybe [Tag]
Maybe Text
Maybe FaqFileFormat
Text
S3Path
roleArn :: Text
s3Path :: S3Path
name :: Text
indexId :: Text
tags :: Maybe [Tag]
languageCode :: Maybe Text
fileFormat :: Maybe FaqFileFormat
description :: Maybe Text
clientToken :: Maybe Text
$sel:roleArn:CreateFaq' :: CreateFaq -> Text
$sel:s3Path:CreateFaq' :: CreateFaq -> S3Path
$sel:name:CreateFaq' :: CreateFaq -> Text
$sel:indexId:CreateFaq' :: CreateFaq -> Text
$sel:tags:CreateFaq' :: CreateFaq -> Maybe [Tag]
$sel:languageCode:CreateFaq' :: CreateFaq -> Maybe Text
$sel:fileFormat:CreateFaq' :: CreateFaq -> Maybe FaqFileFormat
$sel:description:CreateFaq' :: CreateFaq -> Maybe Text
$sel:clientToken:CreateFaq' :: CreateFaq -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ClientToken" 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
clientToken,
            (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
"FileFormat" 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 FaqFileFormat
fileFormat,
            (Key
"LanguageCode" 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
languageCode,
            (Key
"Tags" 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 [Tag]
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"IndexId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
indexId),
            forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name),
            forall a. a -> Maybe a
Prelude.Just (Key
"S3Path" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= S3Path
s3Path),
            forall a. a -> Maybe a
Prelude.Just (Key
"RoleArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
roleArn)
          ]
      )

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

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

-- | /See:/ 'newCreateFaqResponse' smart constructor.
data CreateFaqResponse = CreateFaqResponse'
  { -- | The identifier of the FAQ.
    CreateFaqResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateFaqResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateFaqResponse -> CreateFaqResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateFaqResponse -> CreateFaqResponse -> Bool
$c/= :: CreateFaqResponse -> CreateFaqResponse -> Bool
== :: CreateFaqResponse -> CreateFaqResponse -> Bool
$c== :: CreateFaqResponse -> CreateFaqResponse -> Bool
Prelude.Eq, ReadPrec [CreateFaqResponse]
ReadPrec CreateFaqResponse
Int -> ReadS CreateFaqResponse
ReadS [CreateFaqResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateFaqResponse]
$creadListPrec :: ReadPrec [CreateFaqResponse]
readPrec :: ReadPrec CreateFaqResponse
$creadPrec :: ReadPrec CreateFaqResponse
readList :: ReadS [CreateFaqResponse]
$creadList :: ReadS [CreateFaqResponse]
readsPrec :: Int -> ReadS CreateFaqResponse
$creadsPrec :: Int -> ReadS CreateFaqResponse
Prelude.Read, Int -> CreateFaqResponse -> ShowS
[CreateFaqResponse] -> ShowS
CreateFaqResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateFaqResponse] -> ShowS
$cshowList :: [CreateFaqResponse] -> ShowS
show :: CreateFaqResponse -> String
$cshow :: CreateFaqResponse -> String
showsPrec :: Int -> CreateFaqResponse -> ShowS
$cshowsPrec :: Int -> CreateFaqResponse -> ShowS
Prelude.Show, forall x. Rep CreateFaqResponse x -> CreateFaqResponse
forall x. CreateFaqResponse -> Rep CreateFaqResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateFaqResponse x -> CreateFaqResponse
$cfrom :: forall x. CreateFaqResponse -> Rep CreateFaqResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateFaqResponse' 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:
--
-- 'id', 'createFaqResponse_id' - The identifier of the FAQ.
--
-- 'httpStatus', 'createFaqResponse_httpStatus' - The response's http status code.
newCreateFaqResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateFaqResponse
newCreateFaqResponse :: Int -> CreateFaqResponse
newCreateFaqResponse Int
pHttpStatus_ =
  CreateFaqResponse'
    { $sel:id:CreateFaqResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateFaqResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The identifier of the FAQ.
createFaqResponse_id :: Lens.Lens' CreateFaqResponse (Prelude.Maybe Prelude.Text)
createFaqResponse_id :: Lens' CreateFaqResponse (Maybe Text)
createFaqResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFaqResponse' {Maybe Text
id :: Maybe Text
$sel:id:CreateFaqResponse' :: CreateFaqResponse -> Maybe Text
id} -> Maybe Text
id) (\s :: CreateFaqResponse
s@CreateFaqResponse' {} Maybe Text
a -> CreateFaqResponse
s {$sel:id:CreateFaqResponse' :: Maybe Text
id = Maybe Text
a} :: CreateFaqResponse)

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

instance Prelude.NFData CreateFaqResponse where
  rnf :: CreateFaqResponse -> ()
rnf CreateFaqResponse' {Int
Maybe Text
httpStatus :: Int
id :: Maybe Text
$sel:httpStatus:CreateFaqResponse' :: CreateFaqResponse -> Int
$sel:id:CreateFaqResponse' :: CreateFaqResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
id seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus