{-# 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.Kafka.CreateClusterV2
-- 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 MSK cluster.
module Amazonka.Kafka.CreateClusterV2
  ( -- * Creating a Request
    CreateClusterV2 (..),
    newCreateClusterV2,

    -- * Request Lenses
    createClusterV2_provisioned,
    createClusterV2_serverless,
    createClusterV2_tags,
    createClusterV2_clusterName,

    -- * Destructuring the Response
    CreateClusterV2Response (..),
    newCreateClusterV2Response,

    -- * Response Lenses
    createClusterV2Response_clusterArn,
    createClusterV2Response_clusterName,
    createClusterV2Response_clusterType,
    createClusterV2Response_state,
    createClusterV2Response_httpStatus,
  )
where

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

-- | /See:/ 'newCreateClusterV2' smart constructor.
data CreateClusterV2 = CreateClusterV2'
  { -- | Information about the provisioned cluster.
    CreateClusterV2 -> Maybe ProvisionedRequest
provisioned :: Prelude.Maybe ProvisionedRequest,
    -- | Information about the serverless cluster.
    CreateClusterV2 -> Maybe ServerlessRequest
serverless :: Prelude.Maybe ServerlessRequest,
    -- | A map of tags that you want the cluster to have.
    CreateClusterV2 -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The name of the cluster.
    CreateClusterV2 -> Text
clusterName :: Prelude.Text
  }
  deriving (CreateClusterV2 -> CreateClusterV2 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateClusterV2 -> CreateClusterV2 -> Bool
$c/= :: CreateClusterV2 -> CreateClusterV2 -> Bool
== :: CreateClusterV2 -> CreateClusterV2 -> Bool
$c== :: CreateClusterV2 -> CreateClusterV2 -> Bool
Prelude.Eq, ReadPrec [CreateClusterV2]
ReadPrec CreateClusterV2
Int -> ReadS CreateClusterV2
ReadS [CreateClusterV2]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateClusterV2]
$creadListPrec :: ReadPrec [CreateClusterV2]
readPrec :: ReadPrec CreateClusterV2
$creadPrec :: ReadPrec CreateClusterV2
readList :: ReadS [CreateClusterV2]
$creadList :: ReadS [CreateClusterV2]
readsPrec :: Int -> ReadS CreateClusterV2
$creadsPrec :: Int -> ReadS CreateClusterV2
Prelude.Read, Int -> CreateClusterV2 -> ShowS
[CreateClusterV2] -> ShowS
CreateClusterV2 -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateClusterV2] -> ShowS
$cshowList :: [CreateClusterV2] -> ShowS
show :: CreateClusterV2 -> String
$cshow :: CreateClusterV2 -> String
showsPrec :: Int -> CreateClusterV2 -> ShowS
$cshowsPrec :: Int -> CreateClusterV2 -> ShowS
Prelude.Show, forall x. Rep CreateClusterV2 x -> CreateClusterV2
forall x. CreateClusterV2 -> Rep CreateClusterV2 x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateClusterV2 x -> CreateClusterV2
$cfrom :: forall x. CreateClusterV2 -> Rep CreateClusterV2 x
Prelude.Generic)

-- |
-- Create a value of 'CreateClusterV2' 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:
--
-- 'provisioned', 'createClusterV2_provisioned' - Information about the provisioned cluster.
--
-- 'serverless', 'createClusterV2_serverless' - Information about the serverless cluster.
--
-- 'tags', 'createClusterV2_tags' - A map of tags that you want the cluster to have.
--
-- 'clusterName', 'createClusterV2_clusterName' - The name of the cluster.
newCreateClusterV2 ::
  -- | 'clusterName'
  Prelude.Text ->
  CreateClusterV2
newCreateClusterV2 :: Text -> CreateClusterV2
newCreateClusterV2 Text
pClusterName_ =
  CreateClusterV2'
    { $sel:provisioned:CreateClusterV2' :: Maybe ProvisionedRequest
provisioned = forall a. Maybe a
Prelude.Nothing,
      $sel:serverless:CreateClusterV2' :: Maybe ServerlessRequest
serverless = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateClusterV2' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:clusterName:CreateClusterV2' :: Text
clusterName = Text
pClusterName_
    }

-- | Information about the provisioned cluster.
createClusterV2_provisioned :: Lens.Lens' CreateClusterV2 (Prelude.Maybe ProvisionedRequest)
createClusterV2_provisioned :: Lens' CreateClusterV2 (Maybe ProvisionedRequest)
createClusterV2_provisioned = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClusterV2' {Maybe ProvisionedRequest
provisioned :: Maybe ProvisionedRequest
$sel:provisioned:CreateClusterV2' :: CreateClusterV2 -> Maybe ProvisionedRequest
provisioned} -> Maybe ProvisionedRequest
provisioned) (\s :: CreateClusterV2
s@CreateClusterV2' {} Maybe ProvisionedRequest
a -> CreateClusterV2
s {$sel:provisioned:CreateClusterV2' :: Maybe ProvisionedRequest
provisioned = Maybe ProvisionedRequest
a} :: CreateClusterV2)

-- | Information about the serverless cluster.
createClusterV2_serverless :: Lens.Lens' CreateClusterV2 (Prelude.Maybe ServerlessRequest)
createClusterV2_serverless :: Lens' CreateClusterV2 (Maybe ServerlessRequest)
createClusterV2_serverless = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClusterV2' {Maybe ServerlessRequest
serverless :: Maybe ServerlessRequest
$sel:serverless:CreateClusterV2' :: CreateClusterV2 -> Maybe ServerlessRequest
serverless} -> Maybe ServerlessRequest
serverless) (\s :: CreateClusterV2
s@CreateClusterV2' {} Maybe ServerlessRequest
a -> CreateClusterV2
s {$sel:serverless:CreateClusterV2' :: Maybe ServerlessRequest
serverless = Maybe ServerlessRequest
a} :: CreateClusterV2)

-- | A map of tags that you want the cluster to have.
createClusterV2_tags :: Lens.Lens' CreateClusterV2 (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createClusterV2_tags :: Lens' CreateClusterV2 (Maybe (HashMap Text Text))
createClusterV2_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClusterV2' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateClusterV2' :: CreateClusterV2 -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateClusterV2
s@CreateClusterV2' {} Maybe (HashMap Text Text)
a -> CreateClusterV2
s {$sel:tags:CreateClusterV2' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateClusterV2) 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 name of the cluster.
createClusterV2_clusterName :: Lens.Lens' CreateClusterV2 Prelude.Text
createClusterV2_clusterName :: Lens' CreateClusterV2 Text
createClusterV2_clusterName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClusterV2' {Text
clusterName :: Text
$sel:clusterName:CreateClusterV2' :: CreateClusterV2 -> Text
clusterName} -> Text
clusterName) (\s :: CreateClusterV2
s@CreateClusterV2' {} Text
a -> CreateClusterV2
s {$sel:clusterName:CreateClusterV2' :: Text
clusterName = Text
a} :: CreateClusterV2)

instance Core.AWSRequest CreateClusterV2 where
  type
    AWSResponse CreateClusterV2 =
      CreateClusterV2Response
  request :: (Service -> Service) -> CreateClusterV2 -> Request CreateClusterV2
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 CreateClusterV2
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateClusterV2)))
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 Text
-> Maybe ClusterType
-> Maybe ClusterState
-> Int
-> CreateClusterV2Response
CreateClusterV2Response'
            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
"clusterArn")
            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
"clusterName")
            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
"clusterType")
            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable CreateClusterV2 where
  hashWithSalt :: Int -> CreateClusterV2 -> Int
hashWithSalt Int
_salt CreateClusterV2' {Maybe (HashMap Text Text)
Maybe ProvisionedRequest
Maybe ServerlessRequest
Text
clusterName :: Text
tags :: Maybe (HashMap Text Text)
serverless :: Maybe ServerlessRequest
provisioned :: Maybe ProvisionedRequest
$sel:clusterName:CreateClusterV2' :: CreateClusterV2 -> Text
$sel:tags:CreateClusterV2' :: CreateClusterV2 -> Maybe (HashMap Text Text)
$sel:serverless:CreateClusterV2' :: CreateClusterV2 -> Maybe ServerlessRequest
$sel:provisioned:CreateClusterV2' :: CreateClusterV2 -> Maybe ProvisionedRequest
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ProvisionedRequest
provisioned
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ServerlessRequest
serverless
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clusterName

instance Prelude.NFData CreateClusterV2 where
  rnf :: CreateClusterV2 -> ()
rnf CreateClusterV2' {Maybe (HashMap Text Text)
Maybe ProvisionedRequest
Maybe ServerlessRequest
Text
clusterName :: Text
tags :: Maybe (HashMap Text Text)
serverless :: Maybe ServerlessRequest
provisioned :: Maybe ProvisionedRequest
$sel:clusterName:CreateClusterV2' :: CreateClusterV2 -> Text
$sel:tags:CreateClusterV2' :: CreateClusterV2 -> Maybe (HashMap Text Text)
$sel:serverless:CreateClusterV2' :: CreateClusterV2 -> Maybe ServerlessRequest
$sel:provisioned:CreateClusterV2' :: CreateClusterV2 -> Maybe ProvisionedRequest
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ProvisionedRequest
provisioned
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ServerlessRequest
serverless
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
clusterName

instance Data.ToHeaders CreateClusterV2 where
  toHeaders :: CreateClusterV2 -> 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 CreateClusterV2 where
  toJSON :: CreateClusterV2 -> Value
toJSON CreateClusterV2' {Maybe (HashMap Text Text)
Maybe ProvisionedRequest
Maybe ServerlessRequest
Text
clusterName :: Text
tags :: Maybe (HashMap Text Text)
serverless :: Maybe ServerlessRequest
provisioned :: Maybe ProvisionedRequest
$sel:clusterName:CreateClusterV2' :: CreateClusterV2 -> Text
$sel:tags:CreateClusterV2' :: CreateClusterV2 -> Maybe (HashMap Text Text)
$sel:serverless:CreateClusterV2' :: CreateClusterV2 -> Maybe ServerlessRequest
$sel:provisioned:CreateClusterV2' :: CreateClusterV2 -> Maybe ProvisionedRequest
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"provisioned" 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 ProvisionedRequest
provisioned,
            (Key
"serverless" 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 ServerlessRequest
serverless,
            (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 (HashMap Text Text)
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"clusterName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
clusterName)
          ]
      )

instance Data.ToPath CreateClusterV2 where
  toPath :: CreateClusterV2 -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/api/v2/clusters"

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

-- | /See:/ 'newCreateClusterV2Response' smart constructor.
data CreateClusterV2Response = CreateClusterV2Response'
  { -- | The Amazon Resource Name (ARN) of the cluster.
    CreateClusterV2Response -> Maybe Text
clusterArn :: Prelude.Maybe Prelude.Text,
    -- | The name of the MSK cluster.
    CreateClusterV2Response -> Maybe Text
clusterName :: Prelude.Maybe Prelude.Text,
    -- | The type of the cluster. The possible states are PROVISIONED or
    -- SERVERLESS.
    CreateClusterV2Response -> Maybe ClusterType
clusterType :: Prelude.Maybe ClusterType,
    -- | The state of the cluster. The possible states are ACTIVE, CREATING,
    -- DELETING, FAILED, HEALING, MAINTENANCE, REBOOTING_BROKER, and UPDATING.
    CreateClusterV2Response -> Maybe ClusterState
state :: Prelude.Maybe ClusterState,
    -- | The response's http status code.
    CreateClusterV2Response -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateClusterV2Response -> CreateClusterV2Response -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateClusterV2Response -> CreateClusterV2Response -> Bool
$c/= :: CreateClusterV2Response -> CreateClusterV2Response -> Bool
== :: CreateClusterV2Response -> CreateClusterV2Response -> Bool
$c== :: CreateClusterV2Response -> CreateClusterV2Response -> Bool
Prelude.Eq, ReadPrec [CreateClusterV2Response]
ReadPrec CreateClusterV2Response
Int -> ReadS CreateClusterV2Response
ReadS [CreateClusterV2Response]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateClusterV2Response]
$creadListPrec :: ReadPrec [CreateClusterV2Response]
readPrec :: ReadPrec CreateClusterV2Response
$creadPrec :: ReadPrec CreateClusterV2Response
readList :: ReadS [CreateClusterV2Response]
$creadList :: ReadS [CreateClusterV2Response]
readsPrec :: Int -> ReadS CreateClusterV2Response
$creadsPrec :: Int -> ReadS CreateClusterV2Response
Prelude.Read, Int -> CreateClusterV2Response -> ShowS
[CreateClusterV2Response] -> ShowS
CreateClusterV2Response -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateClusterV2Response] -> ShowS
$cshowList :: [CreateClusterV2Response] -> ShowS
show :: CreateClusterV2Response -> String
$cshow :: CreateClusterV2Response -> String
showsPrec :: Int -> CreateClusterV2Response -> ShowS
$cshowsPrec :: Int -> CreateClusterV2Response -> ShowS
Prelude.Show, forall x. Rep CreateClusterV2Response x -> CreateClusterV2Response
forall x. CreateClusterV2Response -> Rep CreateClusterV2Response x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateClusterV2Response x -> CreateClusterV2Response
$cfrom :: forall x. CreateClusterV2Response -> Rep CreateClusterV2Response x
Prelude.Generic)

-- |
-- Create a value of 'CreateClusterV2Response' 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:
--
-- 'clusterArn', 'createClusterV2Response_clusterArn' - The Amazon Resource Name (ARN) of the cluster.
--
-- 'clusterName', 'createClusterV2Response_clusterName' - The name of the MSK cluster.
--
-- 'clusterType', 'createClusterV2Response_clusterType' - The type of the cluster. The possible states are PROVISIONED or
-- SERVERLESS.
--
-- 'state', 'createClusterV2Response_state' - The state of the cluster. The possible states are ACTIVE, CREATING,
-- DELETING, FAILED, HEALING, MAINTENANCE, REBOOTING_BROKER, and UPDATING.
--
-- 'httpStatus', 'createClusterV2Response_httpStatus' - The response's http status code.
newCreateClusterV2Response ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateClusterV2Response
newCreateClusterV2Response :: Int -> CreateClusterV2Response
newCreateClusterV2Response Int
pHttpStatus_ =
  CreateClusterV2Response'
    { $sel:clusterArn:CreateClusterV2Response' :: Maybe Text
clusterArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:clusterName:CreateClusterV2Response' :: Maybe Text
clusterName = forall a. Maybe a
Prelude.Nothing,
      $sel:clusterType:CreateClusterV2Response' :: Maybe ClusterType
clusterType = forall a. Maybe a
Prelude.Nothing,
      $sel:state:CreateClusterV2Response' :: Maybe ClusterState
state = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateClusterV2Response' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the cluster.
createClusterV2Response_clusterArn :: Lens.Lens' CreateClusterV2Response (Prelude.Maybe Prelude.Text)
createClusterV2Response_clusterArn :: Lens' CreateClusterV2Response (Maybe Text)
createClusterV2Response_clusterArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClusterV2Response' {Maybe Text
clusterArn :: Maybe Text
$sel:clusterArn:CreateClusterV2Response' :: CreateClusterV2Response -> Maybe Text
clusterArn} -> Maybe Text
clusterArn) (\s :: CreateClusterV2Response
s@CreateClusterV2Response' {} Maybe Text
a -> CreateClusterV2Response
s {$sel:clusterArn:CreateClusterV2Response' :: Maybe Text
clusterArn = Maybe Text
a} :: CreateClusterV2Response)

-- | The name of the MSK cluster.
createClusterV2Response_clusterName :: Lens.Lens' CreateClusterV2Response (Prelude.Maybe Prelude.Text)
createClusterV2Response_clusterName :: Lens' CreateClusterV2Response (Maybe Text)
createClusterV2Response_clusterName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClusterV2Response' {Maybe Text
clusterName :: Maybe Text
$sel:clusterName:CreateClusterV2Response' :: CreateClusterV2Response -> Maybe Text
clusterName} -> Maybe Text
clusterName) (\s :: CreateClusterV2Response
s@CreateClusterV2Response' {} Maybe Text
a -> CreateClusterV2Response
s {$sel:clusterName:CreateClusterV2Response' :: Maybe Text
clusterName = Maybe Text
a} :: CreateClusterV2Response)

-- | The type of the cluster. The possible states are PROVISIONED or
-- SERVERLESS.
createClusterV2Response_clusterType :: Lens.Lens' CreateClusterV2Response (Prelude.Maybe ClusterType)
createClusterV2Response_clusterType :: Lens' CreateClusterV2Response (Maybe ClusterType)
createClusterV2Response_clusterType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClusterV2Response' {Maybe ClusterType
clusterType :: Maybe ClusterType
$sel:clusterType:CreateClusterV2Response' :: CreateClusterV2Response -> Maybe ClusterType
clusterType} -> Maybe ClusterType
clusterType) (\s :: CreateClusterV2Response
s@CreateClusterV2Response' {} Maybe ClusterType
a -> CreateClusterV2Response
s {$sel:clusterType:CreateClusterV2Response' :: Maybe ClusterType
clusterType = Maybe ClusterType
a} :: CreateClusterV2Response)

-- | The state of the cluster. The possible states are ACTIVE, CREATING,
-- DELETING, FAILED, HEALING, MAINTENANCE, REBOOTING_BROKER, and UPDATING.
createClusterV2Response_state :: Lens.Lens' CreateClusterV2Response (Prelude.Maybe ClusterState)
createClusterV2Response_state :: Lens' CreateClusterV2Response (Maybe ClusterState)
createClusterV2Response_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClusterV2Response' {Maybe ClusterState
state :: Maybe ClusterState
$sel:state:CreateClusterV2Response' :: CreateClusterV2Response -> Maybe ClusterState
state} -> Maybe ClusterState
state) (\s :: CreateClusterV2Response
s@CreateClusterV2Response' {} Maybe ClusterState
a -> CreateClusterV2Response
s {$sel:state:CreateClusterV2Response' :: Maybe ClusterState
state = Maybe ClusterState
a} :: CreateClusterV2Response)

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

instance Prelude.NFData CreateClusterV2Response where
  rnf :: CreateClusterV2Response -> ()
rnf CreateClusterV2Response' {Int
Maybe Text
Maybe ClusterState
Maybe ClusterType
httpStatus :: Int
state :: Maybe ClusterState
clusterType :: Maybe ClusterType
clusterName :: Maybe Text
clusterArn :: Maybe Text
$sel:httpStatus:CreateClusterV2Response' :: CreateClusterV2Response -> Int
$sel:state:CreateClusterV2Response' :: CreateClusterV2Response -> Maybe ClusterState
$sel:clusterType:CreateClusterV2Response' :: CreateClusterV2Response -> Maybe ClusterType
$sel:clusterName:CreateClusterV2Response' :: CreateClusterV2Response -> Maybe Text
$sel:clusterArn:CreateClusterV2Response' :: CreateClusterV2Response -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clusterArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clusterName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ClusterType
clusterType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ClusterState
state
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus