{-# 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.OpenSearchServerless.CreateCollection
-- 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 a new OpenSearch Serverless collection. For more information,
-- see
-- <https://docs.aws.amazon.com/opensearch-service/latest/developerguide/serverless-manage.html Creating and managing Amazon OpenSearch Serverless collections>.
module Amazonka.OpenSearchServerless.CreateCollection
  ( -- * Creating a Request
    CreateCollection (..),
    newCreateCollection,

    -- * Request Lenses
    createCollection_clientToken,
    createCollection_description,
    createCollection_tags,
    createCollection_type,
    createCollection_name,

    -- * Destructuring the Response
    CreateCollectionResponse (..),
    newCreateCollectionResponse,

    -- * Response Lenses
    createCollectionResponse_createCollectionDetail,
    createCollectionResponse_httpStatus,
  )
where

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

-- | /See:/ 'newCreateCollection' smart constructor.
data CreateCollection = CreateCollection'
  { -- | Unique, case-sensitive identifier to ensure idempotency of the request.
    CreateCollection -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | Description of the collection.
    CreateCollection -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | An arbitrary set of tags (key–value pairs) to associate with the
    -- OpenSearch Serverless collection.
    CreateCollection -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The type of collection.
    CreateCollection -> Maybe CollectionType
type' :: Prelude.Maybe CollectionType,
    -- | Name of the collection.
    CreateCollection -> Text
name :: Prelude.Text
  }
  deriving (CreateCollection -> CreateCollection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateCollection -> CreateCollection -> Bool
$c/= :: CreateCollection -> CreateCollection -> Bool
== :: CreateCollection -> CreateCollection -> Bool
$c== :: CreateCollection -> CreateCollection -> Bool
Prelude.Eq, ReadPrec [CreateCollection]
ReadPrec CreateCollection
Int -> ReadS CreateCollection
ReadS [CreateCollection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateCollection]
$creadListPrec :: ReadPrec [CreateCollection]
readPrec :: ReadPrec CreateCollection
$creadPrec :: ReadPrec CreateCollection
readList :: ReadS [CreateCollection]
$creadList :: ReadS [CreateCollection]
readsPrec :: Int -> ReadS CreateCollection
$creadsPrec :: Int -> ReadS CreateCollection
Prelude.Read, Int -> CreateCollection -> ShowS
[CreateCollection] -> ShowS
CreateCollection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateCollection] -> ShowS
$cshowList :: [CreateCollection] -> ShowS
show :: CreateCollection -> String
$cshow :: CreateCollection -> String
showsPrec :: Int -> CreateCollection -> ShowS
$cshowsPrec :: Int -> CreateCollection -> ShowS
Prelude.Show, forall x. Rep CreateCollection x -> CreateCollection
forall x. CreateCollection -> Rep CreateCollection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateCollection x -> CreateCollection
$cfrom :: forall x. CreateCollection -> Rep CreateCollection x
Prelude.Generic)

-- |
-- Create a value of 'CreateCollection' 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', 'createCollection_clientToken' - Unique, case-sensitive identifier to ensure idempotency of the request.
--
-- 'description', 'createCollection_description' - Description of the collection.
--
-- 'tags', 'createCollection_tags' - An arbitrary set of tags (key–value pairs) to associate with the
-- OpenSearch Serverless collection.
--
-- 'type'', 'createCollection_type' - The type of collection.
--
-- 'name', 'createCollection_name' - Name of the collection.
newCreateCollection ::
  -- | 'name'
  Prelude.Text ->
  CreateCollection
newCreateCollection :: Text -> CreateCollection
newCreateCollection Text
pName_ =
  CreateCollection'
    { $sel:clientToken:CreateCollection' :: Maybe Text
clientToken = forall a. Maybe a
Prelude.Nothing,
      $sel:description:CreateCollection' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateCollection' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:type':CreateCollection' :: Maybe CollectionType
type' = forall a. Maybe a
Prelude.Nothing,
      $sel:name:CreateCollection' :: Text
name = Text
pName_
    }

-- | Unique, case-sensitive identifier to ensure idempotency of the request.
createCollection_clientToken :: Lens.Lens' CreateCollection (Prelude.Maybe Prelude.Text)
createCollection_clientToken :: Lens' CreateCollection (Maybe Text)
createCollection_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCollection' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:CreateCollection' :: CreateCollection -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: CreateCollection
s@CreateCollection' {} Maybe Text
a -> CreateCollection
s {$sel:clientToken:CreateCollection' :: Maybe Text
clientToken = Maybe Text
a} :: CreateCollection)

-- | Description of the collection.
createCollection_description :: Lens.Lens' CreateCollection (Prelude.Maybe Prelude.Text)
createCollection_description :: Lens' CreateCollection (Maybe Text)
createCollection_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCollection' {Maybe Text
description :: Maybe Text
$sel:description:CreateCollection' :: CreateCollection -> Maybe Text
description} -> Maybe Text
description) (\s :: CreateCollection
s@CreateCollection' {} Maybe Text
a -> CreateCollection
s {$sel:description:CreateCollection' :: Maybe Text
description = Maybe Text
a} :: CreateCollection)

-- | An arbitrary set of tags (key–value pairs) to associate with the
-- OpenSearch Serverless collection.
createCollection_tags :: Lens.Lens' CreateCollection (Prelude.Maybe [Tag])
createCollection_tags :: Lens' CreateCollection (Maybe [Tag])
createCollection_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCollection' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateCollection' :: CreateCollection -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateCollection
s@CreateCollection' {} Maybe [Tag]
a -> CreateCollection
s {$sel:tags:CreateCollection' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateCollection) 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 type of collection.
createCollection_type :: Lens.Lens' CreateCollection (Prelude.Maybe CollectionType)
createCollection_type :: Lens' CreateCollection (Maybe CollectionType)
createCollection_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCollection' {Maybe CollectionType
type' :: Maybe CollectionType
$sel:type':CreateCollection' :: CreateCollection -> Maybe CollectionType
type'} -> Maybe CollectionType
type') (\s :: CreateCollection
s@CreateCollection' {} Maybe CollectionType
a -> CreateCollection
s {$sel:type':CreateCollection' :: Maybe CollectionType
type' = Maybe CollectionType
a} :: CreateCollection)

-- | Name of the collection.
createCollection_name :: Lens.Lens' CreateCollection Prelude.Text
createCollection_name :: Lens' CreateCollection Text
createCollection_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCollection' {Text
name :: Text
$sel:name:CreateCollection' :: CreateCollection -> Text
name} -> Text
name) (\s :: CreateCollection
s@CreateCollection' {} Text
a -> CreateCollection
s {$sel:name:CreateCollection' :: Text
name = Text
a} :: CreateCollection)

instance Core.AWSRequest CreateCollection where
  type
    AWSResponse CreateCollection =
      CreateCollectionResponse
  request :: (Service -> Service)
-> CreateCollection -> Request CreateCollection
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 CreateCollection
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateCollection)))
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 CreateCollectionDetail -> Int -> CreateCollectionResponse
CreateCollectionResponse'
            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
"createCollectionDetail")
            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 CreateCollection where
  hashWithSalt :: Int -> CreateCollection -> Int
hashWithSalt Int
_salt CreateCollection' {Maybe [Tag]
Maybe Text
Maybe CollectionType
Text
name :: Text
type' :: Maybe CollectionType
tags :: Maybe [Tag]
description :: Maybe Text
clientToken :: Maybe Text
$sel:name:CreateCollection' :: CreateCollection -> Text
$sel:type':CreateCollection' :: CreateCollection -> Maybe CollectionType
$sel:tags:CreateCollection' :: CreateCollection -> Maybe [Tag]
$sel:description:CreateCollection' :: CreateCollection -> Maybe Text
$sel:clientToken:CreateCollection' :: CreateCollection -> 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 [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CollectionType
type'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData CreateCollection where
  rnf :: CreateCollection -> ()
rnf CreateCollection' {Maybe [Tag]
Maybe Text
Maybe CollectionType
Text
name :: Text
type' :: Maybe CollectionType
tags :: Maybe [Tag]
description :: Maybe Text
clientToken :: Maybe Text
$sel:name:CreateCollection' :: CreateCollection -> Text
$sel:type':CreateCollection' :: CreateCollection -> Maybe CollectionType
$sel:tags:CreateCollection' :: CreateCollection -> Maybe [Tag]
$sel:description:CreateCollection' :: CreateCollection -> Maybe Text
$sel:clientToken:CreateCollection' :: CreateCollection -> 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 [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CollectionType
type'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name

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

instance Data.ToJSON CreateCollection where
  toJSON :: CreateCollection -> Value
toJSON CreateCollection' {Maybe [Tag]
Maybe Text
Maybe CollectionType
Text
name :: Text
type' :: Maybe CollectionType
tags :: Maybe [Tag]
description :: Maybe Text
clientToken :: Maybe Text
$sel:name:CreateCollection' :: CreateCollection -> Text
$sel:type':CreateCollection' :: CreateCollection -> Maybe CollectionType
$sel:tags:CreateCollection' :: CreateCollection -> Maybe [Tag]
$sel:description:CreateCollection' :: CreateCollection -> Maybe Text
$sel:clientToken:CreateCollection' :: CreateCollection -> 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
"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,
            (Key
"type" 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 CollectionType
type',
            forall a. a -> Maybe a
Prelude.Just (Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name)
          ]
      )

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

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

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

-- |
-- Create a value of 'CreateCollectionResponse' 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:
--
-- 'createCollectionDetail', 'createCollectionResponse_createCollectionDetail' - Details about the collection.
--
-- 'httpStatus', 'createCollectionResponse_httpStatus' - The response's http status code.
newCreateCollectionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateCollectionResponse
newCreateCollectionResponse :: Int -> CreateCollectionResponse
newCreateCollectionResponse Int
pHttpStatus_ =
  CreateCollectionResponse'
    { $sel:createCollectionDetail:CreateCollectionResponse' :: Maybe CreateCollectionDetail
createCollectionDetail =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateCollectionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Details about the collection.
createCollectionResponse_createCollectionDetail :: Lens.Lens' CreateCollectionResponse (Prelude.Maybe CreateCollectionDetail)
createCollectionResponse_createCollectionDetail :: Lens' CreateCollectionResponse (Maybe CreateCollectionDetail)
createCollectionResponse_createCollectionDetail = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCollectionResponse' {Maybe CreateCollectionDetail
createCollectionDetail :: Maybe CreateCollectionDetail
$sel:createCollectionDetail:CreateCollectionResponse' :: CreateCollectionResponse -> Maybe CreateCollectionDetail
createCollectionDetail} -> Maybe CreateCollectionDetail
createCollectionDetail) (\s :: CreateCollectionResponse
s@CreateCollectionResponse' {} Maybe CreateCollectionDetail
a -> CreateCollectionResponse
s {$sel:createCollectionDetail:CreateCollectionResponse' :: Maybe CreateCollectionDetail
createCollectionDetail = Maybe CreateCollectionDetail
a} :: CreateCollectionResponse)

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

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