{-# 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.EKS.RegisterCluster
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Connects a Kubernetes cluster to the Amazon EKS control plane.
--
-- Any Kubernetes cluster can be connected to the Amazon EKS control plane
-- to view current information about the cluster and its nodes.
--
-- Cluster connection requires two steps. First, send a
-- @ @@RegisterClusterRequest@@ @ to add it to the Amazon EKS control
-- plane.
--
-- Second, a
-- <https://amazon-eks.s3.us-west-2.amazonaws.com/eks-connector/manifests/eks-connector/latest/eks-connector.yaml Manifest>
-- containing the @activationID@ and @activationCode@ must be applied to
-- the Kubernetes cluster through it\'s native provider to provide
-- visibility.
--
-- After the Manifest is updated and applied, then the connected cluster is
-- visible to the Amazon EKS control plane. If the Manifest is not applied
-- within three days, then the connected cluster will no longer be visible
-- and must be deregistered. See DeregisterCluster.
module Amazonka.EKS.RegisterCluster
  ( -- * Creating a Request
    RegisterCluster (..),
    newRegisterCluster,

    -- * Request Lenses
    registerCluster_clientRequestToken,
    registerCluster_tags,
    registerCluster_name,
    registerCluster_connectorConfig,

    -- * Destructuring the Response
    RegisterClusterResponse (..),
    newRegisterClusterResponse,

    -- * Response Lenses
    registerClusterResponse_cluster,
    registerClusterResponse_httpStatus,
  )
where

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

-- | /See:/ 'newRegisterCluster' smart constructor.
data RegisterCluster = RegisterCluster'
  { -- | Unique, case-sensitive identifier that you provide to ensure the
    -- idempotency of the request.
    RegisterCluster -> Maybe Text
clientRequestToken :: Prelude.Maybe Prelude.Text,
    -- | The metadata that you apply to the cluster to assist with categorization
    -- and organization. Each tag consists of a key and an optional value, both
    -- of which you define. Cluster tags do not propagate to any other
    -- resources associated with the cluster.
    RegisterCluster -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | Define a unique name for this cluster for your Region.
    RegisterCluster -> Text
name :: Prelude.Text,
    -- | The configuration settings required to connect the Kubernetes cluster to
    -- the Amazon EKS control plane.
    RegisterCluster -> ConnectorConfigRequest
connectorConfig :: ConnectorConfigRequest
  }
  deriving (RegisterCluster -> RegisterCluster -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RegisterCluster -> RegisterCluster -> Bool
$c/= :: RegisterCluster -> RegisterCluster -> Bool
== :: RegisterCluster -> RegisterCluster -> Bool
$c== :: RegisterCluster -> RegisterCluster -> Bool
Prelude.Eq, ReadPrec [RegisterCluster]
ReadPrec RegisterCluster
Int -> ReadS RegisterCluster
ReadS [RegisterCluster]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RegisterCluster]
$creadListPrec :: ReadPrec [RegisterCluster]
readPrec :: ReadPrec RegisterCluster
$creadPrec :: ReadPrec RegisterCluster
readList :: ReadS [RegisterCluster]
$creadList :: ReadS [RegisterCluster]
readsPrec :: Int -> ReadS RegisterCluster
$creadsPrec :: Int -> ReadS RegisterCluster
Prelude.Read, Int -> RegisterCluster -> ShowS
[RegisterCluster] -> ShowS
RegisterCluster -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RegisterCluster] -> ShowS
$cshowList :: [RegisterCluster] -> ShowS
show :: RegisterCluster -> String
$cshow :: RegisterCluster -> String
showsPrec :: Int -> RegisterCluster -> ShowS
$cshowsPrec :: Int -> RegisterCluster -> ShowS
Prelude.Show, forall x. Rep RegisterCluster x -> RegisterCluster
forall x. RegisterCluster -> Rep RegisterCluster x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RegisterCluster x -> RegisterCluster
$cfrom :: forall x. RegisterCluster -> Rep RegisterCluster x
Prelude.Generic)

-- |
-- Create a value of 'RegisterCluster' 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:
--
-- 'clientRequestToken', 'registerCluster_clientRequestToken' - Unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the request.
--
-- 'tags', 'registerCluster_tags' - The metadata that you apply to the cluster to assist with categorization
-- and organization. Each tag consists of a key and an optional value, both
-- of which you define. Cluster tags do not propagate to any other
-- resources associated with the cluster.
--
-- 'name', 'registerCluster_name' - Define a unique name for this cluster for your Region.
--
-- 'connectorConfig', 'registerCluster_connectorConfig' - The configuration settings required to connect the Kubernetes cluster to
-- the Amazon EKS control plane.
newRegisterCluster ::
  -- | 'name'
  Prelude.Text ->
  -- | 'connectorConfig'
  ConnectorConfigRequest ->
  RegisterCluster
newRegisterCluster :: Text -> ConnectorConfigRequest -> RegisterCluster
newRegisterCluster Text
pName_ ConnectorConfigRequest
pConnectorConfig_ =
  RegisterCluster'
    { $sel:clientRequestToken:RegisterCluster' :: Maybe Text
clientRequestToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:tags:RegisterCluster' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:name:RegisterCluster' :: Text
name = Text
pName_,
      $sel:connectorConfig:RegisterCluster' :: ConnectorConfigRequest
connectorConfig = ConnectorConfigRequest
pConnectorConfig_
    }

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

-- | The metadata that you apply to the cluster to assist with categorization
-- and organization. Each tag consists of a key and an optional value, both
-- of which you define. Cluster tags do not propagate to any other
-- resources associated with the cluster.
registerCluster_tags :: Lens.Lens' RegisterCluster (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
registerCluster_tags :: Lens' RegisterCluster (Maybe (HashMap Text Text))
registerCluster_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterCluster' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:RegisterCluster' :: RegisterCluster -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: RegisterCluster
s@RegisterCluster' {} Maybe (HashMap Text Text)
a -> RegisterCluster
s {$sel:tags:RegisterCluster' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: RegisterCluster) 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

-- | Define a unique name for this cluster for your Region.
registerCluster_name :: Lens.Lens' RegisterCluster Prelude.Text
registerCluster_name :: Lens' RegisterCluster Text
registerCluster_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterCluster' {Text
name :: Text
$sel:name:RegisterCluster' :: RegisterCluster -> Text
name} -> Text
name) (\s :: RegisterCluster
s@RegisterCluster' {} Text
a -> RegisterCluster
s {$sel:name:RegisterCluster' :: Text
name = Text
a} :: RegisterCluster)

-- | The configuration settings required to connect the Kubernetes cluster to
-- the Amazon EKS control plane.
registerCluster_connectorConfig :: Lens.Lens' RegisterCluster ConnectorConfigRequest
registerCluster_connectorConfig :: Lens' RegisterCluster ConnectorConfigRequest
registerCluster_connectorConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterCluster' {ConnectorConfigRequest
connectorConfig :: ConnectorConfigRequest
$sel:connectorConfig:RegisterCluster' :: RegisterCluster -> ConnectorConfigRequest
connectorConfig} -> ConnectorConfigRequest
connectorConfig) (\s :: RegisterCluster
s@RegisterCluster' {} ConnectorConfigRequest
a -> RegisterCluster
s {$sel:connectorConfig:RegisterCluster' :: ConnectorConfigRequest
connectorConfig = ConnectorConfigRequest
a} :: RegisterCluster)

instance Core.AWSRequest RegisterCluster where
  type
    AWSResponse RegisterCluster =
      RegisterClusterResponse
  request :: (Service -> Service) -> RegisterCluster -> Request RegisterCluster
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 RegisterCluster
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse RegisterCluster)))
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 Cluster -> Int -> RegisterClusterResponse
RegisterClusterResponse'
            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
"cluster")
            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 RegisterCluster where
  hashWithSalt :: Int -> RegisterCluster -> Int
hashWithSalt Int
_salt RegisterCluster' {Maybe Text
Maybe (HashMap Text Text)
Text
ConnectorConfigRequest
connectorConfig :: ConnectorConfigRequest
name :: Text
tags :: Maybe (HashMap Text Text)
clientRequestToken :: Maybe Text
$sel:connectorConfig:RegisterCluster' :: RegisterCluster -> ConnectorConfigRequest
$sel:name:RegisterCluster' :: RegisterCluster -> Text
$sel:tags:RegisterCluster' :: RegisterCluster -> Maybe (HashMap Text Text)
$sel:clientRequestToken:RegisterCluster' :: RegisterCluster -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientRequestToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ConnectorConfigRequest
connectorConfig

instance Prelude.NFData RegisterCluster where
  rnf :: RegisterCluster -> ()
rnf RegisterCluster' {Maybe Text
Maybe (HashMap Text Text)
Text
ConnectorConfigRequest
connectorConfig :: ConnectorConfigRequest
name :: Text
tags :: Maybe (HashMap Text Text)
clientRequestToken :: Maybe Text
$sel:connectorConfig:RegisterCluster' :: RegisterCluster -> ConnectorConfigRequest
$sel:name:RegisterCluster' :: RegisterCluster -> Text
$sel:tags:RegisterCluster' :: RegisterCluster -> Maybe (HashMap Text Text)
$sel:clientRequestToken:RegisterCluster' :: RegisterCluster -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientRequestToken
      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
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ConnectorConfigRequest
connectorConfig

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

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

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

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

-- |
-- Create a value of 'RegisterClusterResponse' 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:
--
-- 'cluster', 'registerClusterResponse_cluster' - Undocumented member.
--
-- 'httpStatus', 'registerClusterResponse_httpStatus' - The response's http status code.
newRegisterClusterResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  RegisterClusterResponse
newRegisterClusterResponse :: Int -> RegisterClusterResponse
newRegisterClusterResponse Int
pHttpStatus_ =
  RegisterClusterResponse'
    { $sel:cluster:RegisterClusterResponse' :: Maybe Cluster
cluster = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:RegisterClusterResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
registerClusterResponse_cluster :: Lens.Lens' RegisterClusterResponse (Prelude.Maybe Cluster)
registerClusterResponse_cluster :: Lens' RegisterClusterResponse (Maybe Cluster)
registerClusterResponse_cluster = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterClusterResponse' {Maybe Cluster
cluster :: Maybe Cluster
$sel:cluster:RegisterClusterResponse' :: RegisterClusterResponse -> Maybe Cluster
cluster} -> Maybe Cluster
cluster) (\s :: RegisterClusterResponse
s@RegisterClusterResponse' {} Maybe Cluster
a -> RegisterClusterResponse
s {$sel:cluster:RegisterClusterResponse' :: Maybe Cluster
cluster = Maybe Cluster
a} :: RegisterClusterResponse)

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

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