{-# 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.CreateNodegroup
-- 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 managed node group for an Amazon EKS cluster. You can only
-- create a node group for your cluster that is equal to the current
-- Kubernetes version for the cluster. All node groups are created with the
-- latest AMI release version for the respective minor Kubernetes version
-- of the cluster, unless you deploy a custom AMI using a launch template.
-- For more information about using launch templates, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/launch-templates.html Launch template support>.
--
-- An Amazon EKS managed node group is an Amazon EC2 Auto Scaling group and
-- associated Amazon EC2 instances that are managed by Amazon Web Services
-- for an Amazon EKS cluster. For more information, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/managed-node-groups.html Managed node groups>
-- in the /Amazon EKS User Guide/.
--
-- Windows AMI types are only supported for commercial Regions that support
-- Windows Amazon EKS.
module Amazonka.EKS.CreateNodegroup
  ( -- * Creating a Request
    CreateNodegroup (..),
    newCreateNodegroup,

    -- * Request Lenses
    createNodegroup_amiType,
    createNodegroup_capacityType,
    createNodegroup_clientRequestToken,
    createNodegroup_diskSize,
    createNodegroup_instanceTypes,
    createNodegroup_labels,
    createNodegroup_launchTemplate,
    createNodegroup_releaseVersion,
    createNodegroup_remoteAccess,
    createNodegroup_scalingConfig,
    createNodegroup_tags,
    createNodegroup_taints,
    createNodegroup_updateConfig,
    createNodegroup_version,
    createNodegroup_clusterName,
    createNodegroup_nodegroupName,
    createNodegroup_subnets,
    createNodegroup_nodeRole,

    -- * Destructuring the Response
    CreateNodegroupResponse (..),
    newCreateNodegroupResponse,

    -- * Response Lenses
    createNodegroupResponse_nodegroup,
    createNodegroupResponse_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:/ 'newCreateNodegroup' smart constructor.
data CreateNodegroup = CreateNodegroup'
  { -- | The AMI type for your node group. If you specify @launchTemplate@, and
    -- your launch template uses a custom AMI, then don\'t specify @amiType@,
    -- or the node group deployment will fail. If your launch template uses a
    -- Windows custom AMI, then add @eks:kube-proxy-windows@ to your Windows
    -- nodes @rolearn@ in the @aws-auth@ @ConfigMap@. For more information
    -- about using launch templates with Amazon EKS, see
    -- <https://docs.aws.amazon.com/eks/latest/userguide/launch-templates.html Launch template support>
    -- in the /Amazon EKS User Guide/.
    CreateNodegroup -> Maybe AMITypes
amiType :: Prelude.Maybe AMITypes,
    -- | The capacity type for your node group.
    CreateNodegroup -> Maybe CapacityTypes
capacityType :: Prelude.Maybe CapacityTypes,
    -- | Unique, case-sensitive identifier that you provide to ensure the
    -- idempotency of the request.
    CreateNodegroup -> Maybe Text
clientRequestToken :: Prelude.Maybe Prelude.Text,
    -- | The root device disk size (in GiB) for your node group instances. The
    -- default disk size is 20 GiB for Linux and Bottlerocket. The default disk
    -- size is 50 GiB for Windows. If you specify @launchTemplate@, then don\'t
    -- specify @diskSize@, or the node group deployment will fail. For more
    -- information about using launch templates with Amazon EKS, see
    -- <https://docs.aws.amazon.com/eks/latest/userguide/launch-templates.html Launch template support>
    -- in the /Amazon EKS User Guide/.
    CreateNodegroup -> Maybe Int
diskSize :: Prelude.Maybe Prelude.Int,
    -- | Specify the instance types for a node group. If you specify a GPU
    -- instance type, make sure to also specify an applicable GPU AMI type with
    -- the @amiType@ parameter. If you specify @launchTemplate@, then you can
    -- specify zero or one instance type in your launch template /or/ you can
    -- specify 0-20 instance types for @instanceTypes@. If however, you specify
    -- an instance type in your launch template /and/ specify any
    -- @instanceTypes@, the node group deployment will fail. If you don\'t
    -- specify an instance type in a launch template or for @instanceTypes@,
    -- then @t3.medium@ is used, by default. If you specify @Spot@ for
    -- @capacityType@, then we recommend specifying multiple values for
    -- @instanceTypes@. For more information, see
    -- <https://docs.aws.amazon.com/eks/latest/userguide/managed-node-groups.html#managed-node-group-capacity-types Managed node group capacity types>
    -- and
    -- <https://docs.aws.amazon.com/eks/latest/userguide/launch-templates.html Launch template support>
    -- in the /Amazon EKS User Guide/.
    CreateNodegroup -> Maybe [Text]
instanceTypes :: Prelude.Maybe [Prelude.Text],
    -- | The Kubernetes labels to be applied to the nodes in the node group when
    -- they are created.
    CreateNodegroup -> Maybe (HashMap Text Text)
labels :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | An object representing a node group\'s launch template specification. If
    -- specified, then do not specify @instanceTypes@, @diskSize@, or
    -- @remoteAccess@ and make sure that the launch template meets the
    -- requirements in @launchTemplateSpecification@.
    CreateNodegroup -> Maybe LaunchTemplateSpecification
launchTemplate :: Prelude.Maybe LaunchTemplateSpecification,
    -- | The AMI version of the Amazon EKS optimized AMI to use with your node
    -- group. By default, the latest available AMI version for the node
    -- group\'s current Kubernetes version is used. For information about Linux
    -- versions, see
    -- <https://docs.aws.amazon.com/eks/latest/userguide/eks-linux-ami-versions.html Amazon EKS optimized Amazon Linux AMI versions>
    -- in the /Amazon EKS User Guide/. Amazon EKS managed node groups support
    -- the November 2022 and later releases of the Windows AMIs. For
    -- information about Windows versions, see
    -- <https://docs.aws.amazon.com/eks/latest/userguide/eks-ami-versions-windows.html Amazon EKS optimized Windows AMI versions>
    -- in the /Amazon EKS User Guide/.
    --
    -- If you specify @launchTemplate@, and your launch template uses a custom
    -- AMI, then don\'t specify @releaseVersion@, or the node group deployment
    -- will fail. For more information about using launch templates with Amazon
    -- EKS, see
    -- <https://docs.aws.amazon.com/eks/latest/userguide/launch-templates.html Launch template support>
    -- in the /Amazon EKS User Guide/.
    CreateNodegroup -> Maybe Text
releaseVersion :: Prelude.Maybe Prelude.Text,
    -- | The remote access configuration to use with your node group. For Linux,
    -- the protocol is SSH. For Windows, the protocol is RDP. If you specify
    -- @launchTemplate@, then don\'t specify @remoteAccess@, or the node group
    -- deployment will fail. For more information about using launch templates
    -- with Amazon EKS, see
    -- <https://docs.aws.amazon.com/eks/latest/userguide/launch-templates.html Launch template support>
    -- in the /Amazon EKS User Guide/.
    CreateNodegroup -> Maybe RemoteAccessConfig
remoteAccess :: Prelude.Maybe RemoteAccessConfig,
    -- | The scaling configuration details for the Auto Scaling group that is
    -- created for your node group.
    CreateNodegroup -> Maybe NodegroupScalingConfig
scalingConfig :: Prelude.Maybe NodegroupScalingConfig,
    -- | The metadata to apply to the node group to assist with categorization
    -- and organization. Each tag consists of a key and an optional value. You
    -- define both. Node group tags do not propagate to any other resources
    -- associated with the node group, such as the Amazon EC2 instances or
    -- subnets.
    CreateNodegroup -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The Kubernetes taints to be applied to the nodes in the node group. For
    -- more information, see
    -- <https://docs.aws.amazon.com/eks/latest/userguide/node-taints-managed-node-groups.html Node taints on managed node groups>.
    CreateNodegroup -> Maybe [Taint]
taints :: Prelude.Maybe [Taint],
    -- | The node group update configuration.
    CreateNodegroup -> Maybe NodegroupUpdateConfig
updateConfig :: Prelude.Maybe NodegroupUpdateConfig,
    -- | The Kubernetes version to use for your managed nodes. By default, the
    -- Kubernetes version of the cluster is used, and this is the only accepted
    -- specified value. If you specify @launchTemplate@, and your launch
    -- template uses a custom AMI, then don\'t specify @version@, or the node
    -- group deployment will fail. For more information about using launch
    -- templates with Amazon EKS, see
    -- <https://docs.aws.amazon.com/eks/latest/userguide/launch-templates.html Launch template support>
    -- in the /Amazon EKS User Guide/.
    CreateNodegroup -> Maybe Text
version :: Prelude.Maybe Prelude.Text,
    -- | The name of the cluster to create the node group in.
    CreateNodegroup -> Text
clusterName :: Prelude.Text,
    -- | The unique name to give your node group.
    CreateNodegroup -> Text
nodegroupName :: Prelude.Text,
    -- | The subnets to use for the Auto Scaling group that is created for your
    -- node group. If you specify @launchTemplate@, then don\'t specify
    -- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_CreateNetworkInterface.html SubnetId>
    -- in your launch template, or the node group deployment will fail. For
    -- more information about using launch templates with Amazon EKS, see
    -- <https://docs.aws.amazon.com/eks/latest/userguide/launch-templates.html Launch template support>
    -- in the /Amazon EKS User Guide/.
    CreateNodegroup -> [Text]
subnets :: [Prelude.Text],
    -- | The Amazon Resource Name (ARN) of the IAM role to associate with your
    -- node group. The Amazon EKS worker node @kubelet@ daemon makes calls to
    -- Amazon Web Services APIs on your behalf. Nodes receive permissions for
    -- these API calls through an IAM instance profile and associated policies.
    -- Before you can launch nodes and register them into a cluster, you must
    -- create an IAM role for those nodes to use when they are launched. For
    -- more information, see
    -- <https://docs.aws.amazon.com/eks/latest/userguide/create-node-role.html Amazon EKS node IAM role>
    -- in the //Amazon EKS User Guide// . If you specify @launchTemplate@, then
    -- don\'t specify
    -- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_IamInstanceProfile.html IamInstanceProfile>
    -- in your launch template, or the node group deployment will fail. For
    -- more information about using launch templates with Amazon EKS, see
    -- <https://docs.aws.amazon.com/eks/latest/userguide/launch-templates.html Launch template support>
    -- in the /Amazon EKS User Guide/.
    CreateNodegroup -> Text
nodeRole :: Prelude.Text
  }
  deriving (CreateNodegroup -> CreateNodegroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateNodegroup -> CreateNodegroup -> Bool
$c/= :: CreateNodegroup -> CreateNodegroup -> Bool
== :: CreateNodegroup -> CreateNodegroup -> Bool
$c== :: CreateNodegroup -> CreateNodegroup -> Bool
Prelude.Eq, ReadPrec [CreateNodegroup]
ReadPrec CreateNodegroup
Int -> ReadS CreateNodegroup
ReadS [CreateNodegroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateNodegroup]
$creadListPrec :: ReadPrec [CreateNodegroup]
readPrec :: ReadPrec CreateNodegroup
$creadPrec :: ReadPrec CreateNodegroup
readList :: ReadS [CreateNodegroup]
$creadList :: ReadS [CreateNodegroup]
readsPrec :: Int -> ReadS CreateNodegroup
$creadsPrec :: Int -> ReadS CreateNodegroup
Prelude.Read, Int -> CreateNodegroup -> ShowS
[CreateNodegroup] -> ShowS
CreateNodegroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateNodegroup] -> ShowS
$cshowList :: [CreateNodegroup] -> ShowS
show :: CreateNodegroup -> String
$cshow :: CreateNodegroup -> String
showsPrec :: Int -> CreateNodegroup -> ShowS
$cshowsPrec :: Int -> CreateNodegroup -> ShowS
Prelude.Show, forall x. Rep CreateNodegroup x -> CreateNodegroup
forall x. CreateNodegroup -> Rep CreateNodegroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateNodegroup x -> CreateNodegroup
$cfrom :: forall x. CreateNodegroup -> Rep CreateNodegroup x
Prelude.Generic)

-- |
-- Create a value of 'CreateNodegroup' 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:
--
-- 'amiType', 'createNodegroup_amiType' - The AMI type for your node group. If you specify @launchTemplate@, and
-- your launch template uses a custom AMI, then don\'t specify @amiType@,
-- or the node group deployment will fail. If your launch template uses a
-- Windows custom AMI, then add @eks:kube-proxy-windows@ to your Windows
-- nodes @rolearn@ in the @aws-auth@ @ConfigMap@. For more information
-- about using launch templates with Amazon EKS, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/launch-templates.html Launch template support>
-- in the /Amazon EKS User Guide/.
--
-- 'capacityType', 'createNodegroup_capacityType' - The capacity type for your node group.
--
-- 'clientRequestToken', 'createNodegroup_clientRequestToken' - Unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the request.
--
-- 'diskSize', 'createNodegroup_diskSize' - The root device disk size (in GiB) for your node group instances. The
-- default disk size is 20 GiB for Linux and Bottlerocket. The default disk
-- size is 50 GiB for Windows. If you specify @launchTemplate@, then don\'t
-- specify @diskSize@, or the node group deployment will fail. For more
-- information about using launch templates with Amazon EKS, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/launch-templates.html Launch template support>
-- in the /Amazon EKS User Guide/.
--
-- 'instanceTypes', 'createNodegroup_instanceTypes' - Specify the instance types for a node group. If you specify a GPU
-- instance type, make sure to also specify an applicable GPU AMI type with
-- the @amiType@ parameter. If you specify @launchTemplate@, then you can
-- specify zero or one instance type in your launch template /or/ you can
-- specify 0-20 instance types for @instanceTypes@. If however, you specify
-- an instance type in your launch template /and/ specify any
-- @instanceTypes@, the node group deployment will fail. If you don\'t
-- specify an instance type in a launch template or for @instanceTypes@,
-- then @t3.medium@ is used, by default. If you specify @Spot@ for
-- @capacityType@, then we recommend specifying multiple values for
-- @instanceTypes@. For more information, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/managed-node-groups.html#managed-node-group-capacity-types Managed node group capacity types>
-- and
-- <https://docs.aws.amazon.com/eks/latest/userguide/launch-templates.html Launch template support>
-- in the /Amazon EKS User Guide/.
--
-- 'labels', 'createNodegroup_labels' - The Kubernetes labels to be applied to the nodes in the node group when
-- they are created.
--
-- 'launchTemplate', 'createNodegroup_launchTemplate' - An object representing a node group\'s launch template specification. If
-- specified, then do not specify @instanceTypes@, @diskSize@, or
-- @remoteAccess@ and make sure that the launch template meets the
-- requirements in @launchTemplateSpecification@.
--
-- 'releaseVersion', 'createNodegroup_releaseVersion' - The AMI version of the Amazon EKS optimized AMI to use with your node
-- group. By default, the latest available AMI version for the node
-- group\'s current Kubernetes version is used. For information about Linux
-- versions, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/eks-linux-ami-versions.html Amazon EKS optimized Amazon Linux AMI versions>
-- in the /Amazon EKS User Guide/. Amazon EKS managed node groups support
-- the November 2022 and later releases of the Windows AMIs. For
-- information about Windows versions, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/eks-ami-versions-windows.html Amazon EKS optimized Windows AMI versions>
-- in the /Amazon EKS User Guide/.
--
-- If you specify @launchTemplate@, and your launch template uses a custom
-- AMI, then don\'t specify @releaseVersion@, or the node group deployment
-- will fail. For more information about using launch templates with Amazon
-- EKS, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/launch-templates.html Launch template support>
-- in the /Amazon EKS User Guide/.
--
-- 'remoteAccess', 'createNodegroup_remoteAccess' - The remote access configuration to use with your node group. For Linux,
-- the protocol is SSH. For Windows, the protocol is RDP. If you specify
-- @launchTemplate@, then don\'t specify @remoteAccess@, or the node group
-- deployment will fail. For more information about using launch templates
-- with Amazon EKS, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/launch-templates.html Launch template support>
-- in the /Amazon EKS User Guide/.
--
-- 'scalingConfig', 'createNodegroup_scalingConfig' - The scaling configuration details for the Auto Scaling group that is
-- created for your node group.
--
-- 'tags', 'createNodegroup_tags' - The metadata to apply to the node group to assist with categorization
-- and organization. Each tag consists of a key and an optional value. You
-- define both. Node group tags do not propagate to any other resources
-- associated with the node group, such as the Amazon EC2 instances or
-- subnets.
--
-- 'taints', 'createNodegroup_taints' - The Kubernetes taints to be applied to the nodes in the node group. For
-- more information, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/node-taints-managed-node-groups.html Node taints on managed node groups>.
--
-- 'updateConfig', 'createNodegroup_updateConfig' - The node group update configuration.
--
-- 'version', 'createNodegroup_version' - The Kubernetes version to use for your managed nodes. By default, the
-- Kubernetes version of the cluster is used, and this is the only accepted
-- specified value. If you specify @launchTemplate@, and your launch
-- template uses a custom AMI, then don\'t specify @version@, or the node
-- group deployment will fail. For more information about using launch
-- templates with Amazon EKS, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/launch-templates.html Launch template support>
-- in the /Amazon EKS User Guide/.
--
-- 'clusterName', 'createNodegroup_clusterName' - The name of the cluster to create the node group in.
--
-- 'nodegroupName', 'createNodegroup_nodegroupName' - The unique name to give your node group.
--
-- 'subnets', 'createNodegroup_subnets' - The subnets to use for the Auto Scaling group that is created for your
-- node group. If you specify @launchTemplate@, then don\'t specify
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_CreateNetworkInterface.html SubnetId>
-- in your launch template, or the node group deployment will fail. For
-- more information about using launch templates with Amazon EKS, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/launch-templates.html Launch template support>
-- in the /Amazon EKS User Guide/.
--
-- 'nodeRole', 'createNodegroup_nodeRole' - The Amazon Resource Name (ARN) of the IAM role to associate with your
-- node group. The Amazon EKS worker node @kubelet@ daemon makes calls to
-- Amazon Web Services APIs on your behalf. Nodes receive permissions for
-- these API calls through an IAM instance profile and associated policies.
-- Before you can launch nodes and register them into a cluster, you must
-- create an IAM role for those nodes to use when they are launched. For
-- more information, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/create-node-role.html Amazon EKS node IAM role>
-- in the //Amazon EKS User Guide// . If you specify @launchTemplate@, then
-- don\'t specify
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_IamInstanceProfile.html IamInstanceProfile>
-- in your launch template, or the node group deployment will fail. For
-- more information about using launch templates with Amazon EKS, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/launch-templates.html Launch template support>
-- in the /Amazon EKS User Guide/.
newCreateNodegroup ::
  -- | 'clusterName'
  Prelude.Text ->
  -- | 'nodegroupName'
  Prelude.Text ->
  -- | 'nodeRole'
  Prelude.Text ->
  CreateNodegroup
newCreateNodegroup :: Text -> Text -> Text -> CreateNodegroup
newCreateNodegroup
  Text
pClusterName_
  Text
pNodegroupName_
  Text
pNodeRole_ =
    CreateNodegroup'
      { $sel:amiType:CreateNodegroup' :: Maybe AMITypes
amiType = forall a. Maybe a
Prelude.Nothing,
        $sel:capacityType:CreateNodegroup' :: Maybe CapacityTypes
capacityType = forall a. Maybe a
Prelude.Nothing,
        $sel:clientRequestToken:CreateNodegroup' :: Maybe Text
clientRequestToken = forall a. Maybe a
Prelude.Nothing,
        $sel:diskSize:CreateNodegroup' :: Maybe Int
diskSize = forall a. Maybe a
Prelude.Nothing,
        $sel:instanceTypes:CreateNodegroup' :: Maybe [Text]
instanceTypes = forall a. Maybe a
Prelude.Nothing,
        $sel:labels:CreateNodegroup' :: Maybe (HashMap Text Text)
labels = forall a. Maybe a
Prelude.Nothing,
        $sel:launchTemplate:CreateNodegroup' :: Maybe LaunchTemplateSpecification
launchTemplate = forall a. Maybe a
Prelude.Nothing,
        $sel:releaseVersion:CreateNodegroup' :: Maybe Text
releaseVersion = forall a. Maybe a
Prelude.Nothing,
        $sel:remoteAccess:CreateNodegroup' :: Maybe RemoteAccessConfig
remoteAccess = forall a. Maybe a
Prelude.Nothing,
        $sel:scalingConfig:CreateNodegroup' :: Maybe NodegroupScalingConfig
scalingConfig = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:CreateNodegroup' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:taints:CreateNodegroup' :: Maybe [Taint]
taints = forall a. Maybe a
Prelude.Nothing,
        $sel:updateConfig:CreateNodegroup' :: Maybe NodegroupUpdateConfig
updateConfig = forall a. Maybe a
Prelude.Nothing,
        $sel:version:CreateNodegroup' :: Maybe Text
version = forall a. Maybe a
Prelude.Nothing,
        $sel:clusterName:CreateNodegroup' :: Text
clusterName = Text
pClusterName_,
        $sel:nodegroupName:CreateNodegroup' :: Text
nodegroupName = Text
pNodegroupName_,
        $sel:subnets:CreateNodegroup' :: [Text]
subnets = forall a. Monoid a => a
Prelude.mempty,
        $sel:nodeRole:CreateNodegroup' :: Text
nodeRole = Text
pNodeRole_
      }

-- | The AMI type for your node group. If you specify @launchTemplate@, and
-- your launch template uses a custom AMI, then don\'t specify @amiType@,
-- or the node group deployment will fail. If your launch template uses a
-- Windows custom AMI, then add @eks:kube-proxy-windows@ to your Windows
-- nodes @rolearn@ in the @aws-auth@ @ConfigMap@. For more information
-- about using launch templates with Amazon EKS, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/launch-templates.html Launch template support>
-- in the /Amazon EKS User Guide/.
createNodegroup_amiType :: Lens.Lens' CreateNodegroup (Prelude.Maybe AMITypes)
createNodegroup_amiType :: Lens' CreateNodegroup (Maybe AMITypes)
createNodegroup_amiType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNodegroup' {Maybe AMITypes
amiType :: Maybe AMITypes
$sel:amiType:CreateNodegroup' :: CreateNodegroup -> Maybe AMITypes
amiType} -> Maybe AMITypes
amiType) (\s :: CreateNodegroup
s@CreateNodegroup' {} Maybe AMITypes
a -> CreateNodegroup
s {$sel:amiType:CreateNodegroup' :: Maybe AMITypes
amiType = Maybe AMITypes
a} :: CreateNodegroup)

-- | The capacity type for your node group.
createNodegroup_capacityType :: Lens.Lens' CreateNodegroup (Prelude.Maybe CapacityTypes)
createNodegroup_capacityType :: Lens' CreateNodegroup (Maybe CapacityTypes)
createNodegroup_capacityType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNodegroup' {Maybe CapacityTypes
capacityType :: Maybe CapacityTypes
$sel:capacityType:CreateNodegroup' :: CreateNodegroup -> Maybe CapacityTypes
capacityType} -> Maybe CapacityTypes
capacityType) (\s :: CreateNodegroup
s@CreateNodegroup' {} Maybe CapacityTypes
a -> CreateNodegroup
s {$sel:capacityType:CreateNodegroup' :: Maybe CapacityTypes
capacityType = Maybe CapacityTypes
a} :: CreateNodegroup)

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

-- | The root device disk size (in GiB) for your node group instances. The
-- default disk size is 20 GiB for Linux and Bottlerocket. The default disk
-- size is 50 GiB for Windows. If you specify @launchTemplate@, then don\'t
-- specify @diskSize@, or the node group deployment will fail. For more
-- information about using launch templates with Amazon EKS, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/launch-templates.html Launch template support>
-- in the /Amazon EKS User Guide/.
createNodegroup_diskSize :: Lens.Lens' CreateNodegroup (Prelude.Maybe Prelude.Int)
createNodegroup_diskSize :: Lens' CreateNodegroup (Maybe Int)
createNodegroup_diskSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNodegroup' {Maybe Int
diskSize :: Maybe Int
$sel:diskSize:CreateNodegroup' :: CreateNodegroup -> Maybe Int
diskSize} -> Maybe Int
diskSize) (\s :: CreateNodegroup
s@CreateNodegroup' {} Maybe Int
a -> CreateNodegroup
s {$sel:diskSize:CreateNodegroup' :: Maybe Int
diskSize = Maybe Int
a} :: CreateNodegroup)

-- | Specify the instance types for a node group. If you specify a GPU
-- instance type, make sure to also specify an applicable GPU AMI type with
-- the @amiType@ parameter. If you specify @launchTemplate@, then you can
-- specify zero or one instance type in your launch template /or/ you can
-- specify 0-20 instance types for @instanceTypes@. If however, you specify
-- an instance type in your launch template /and/ specify any
-- @instanceTypes@, the node group deployment will fail. If you don\'t
-- specify an instance type in a launch template or for @instanceTypes@,
-- then @t3.medium@ is used, by default. If you specify @Spot@ for
-- @capacityType@, then we recommend specifying multiple values for
-- @instanceTypes@. For more information, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/managed-node-groups.html#managed-node-group-capacity-types Managed node group capacity types>
-- and
-- <https://docs.aws.amazon.com/eks/latest/userguide/launch-templates.html Launch template support>
-- in the /Amazon EKS User Guide/.
createNodegroup_instanceTypes :: Lens.Lens' CreateNodegroup (Prelude.Maybe [Prelude.Text])
createNodegroup_instanceTypes :: Lens' CreateNodegroup (Maybe [Text])
createNodegroup_instanceTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNodegroup' {Maybe [Text]
instanceTypes :: Maybe [Text]
$sel:instanceTypes:CreateNodegroup' :: CreateNodegroup -> Maybe [Text]
instanceTypes} -> Maybe [Text]
instanceTypes) (\s :: CreateNodegroup
s@CreateNodegroup' {} Maybe [Text]
a -> CreateNodegroup
s {$sel:instanceTypes:CreateNodegroup' :: Maybe [Text]
instanceTypes = Maybe [Text]
a} :: CreateNodegroup) 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 Kubernetes labels to be applied to the nodes in the node group when
-- they are created.
createNodegroup_labels :: Lens.Lens' CreateNodegroup (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createNodegroup_labels :: Lens' CreateNodegroup (Maybe (HashMap Text Text))
createNodegroup_labels = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNodegroup' {Maybe (HashMap Text Text)
labels :: Maybe (HashMap Text Text)
$sel:labels:CreateNodegroup' :: CreateNodegroup -> Maybe (HashMap Text Text)
labels} -> Maybe (HashMap Text Text)
labels) (\s :: CreateNodegroup
s@CreateNodegroup' {} Maybe (HashMap Text Text)
a -> CreateNodegroup
s {$sel:labels:CreateNodegroup' :: Maybe (HashMap Text Text)
labels = Maybe (HashMap Text Text)
a} :: CreateNodegroup) 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

-- | An object representing a node group\'s launch template specification. If
-- specified, then do not specify @instanceTypes@, @diskSize@, or
-- @remoteAccess@ and make sure that the launch template meets the
-- requirements in @launchTemplateSpecification@.
createNodegroup_launchTemplate :: Lens.Lens' CreateNodegroup (Prelude.Maybe LaunchTemplateSpecification)
createNodegroup_launchTemplate :: Lens' CreateNodegroup (Maybe LaunchTemplateSpecification)
createNodegroup_launchTemplate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNodegroup' {Maybe LaunchTemplateSpecification
launchTemplate :: Maybe LaunchTemplateSpecification
$sel:launchTemplate:CreateNodegroup' :: CreateNodegroup -> Maybe LaunchTemplateSpecification
launchTemplate} -> Maybe LaunchTemplateSpecification
launchTemplate) (\s :: CreateNodegroup
s@CreateNodegroup' {} Maybe LaunchTemplateSpecification
a -> CreateNodegroup
s {$sel:launchTemplate:CreateNodegroup' :: Maybe LaunchTemplateSpecification
launchTemplate = Maybe LaunchTemplateSpecification
a} :: CreateNodegroup)

-- | The AMI version of the Amazon EKS optimized AMI to use with your node
-- group. By default, the latest available AMI version for the node
-- group\'s current Kubernetes version is used. For information about Linux
-- versions, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/eks-linux-ami-versions.html Amazon EKS optimized Amazon Linux AMI versions>
-- in the /Amazon EKS User Guide/. Amazon EKS managed node groups support
-- the November 2022 and later releases of the Windows AMIs. For
-- information about Windows versions, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/eks-ami-versions-windows.html Amazon EKS optimized Windows AMI versions>
-- in the /Amazon EKS User Guide/.
--
-- If you specify @launchTemplate@, and your launch template uses a custom
-- AMI, then don\'t specify @releaseVersion@, or the node group deployment
-- will fail. For more information about using launch templates with Amazon
-- EKS, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/launch-templates.html Launch template support>
-- in the /Amazon EKS User Guide/.
createNodegroup_releaseVersion :: Lens.Lens' CreateNodegroup (Prelude.Maybe Prelude.Text)
createNodegroup_releaseVersion :: Lens' CreateNodegroup (Maybe Text)
createNodegroup_releaseVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNodegroup' {Maybe Text
releaseVersion :: Maybe Text
$sel:releaseVersion:CreateNodegroup' :: CreateNodegroup -> Maybe Text
releaseVersion} -> Maybe Text
releaseVersion) (\s :: CreateNodegroup
s@CreateNodegroup' {} Maybe Text
a -> CreateNodegroup
s {$sel:releaseVersion:CreateNodegroup' :: Maybe Text
releaseVersion = Maybe Text
a} :: CreateNodegroup)

-- | The remote access configuration to use with your node group. For Linux,
-- the protocol is SSH. For Windows, the protocol is RDP. If you specify
-- @launchTemplate@, then don\'t specify @remoteAccess@, or the node group
-- deployment will fail. For more information about using launch templates
-- with Amazon EKS, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/launch-templates.html Launch template support>
-- in the /Amazon EKS User Guide/.
createNodegroup_remoteAccess :: Lens.Lens' CreateNodegroup (Prelude.Maybe RemoteAccessConfig)
createNodegroup_remoteAccess :: Lens' CreateNodegroup (Maybe RemoteAccessConfig)
createNodegroup_remoteAccess = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNodegroup' {Maybe RemoteAccessConfig
remoteAccess :: Maybe RemoteAccessConfig
$sel:remoteAccess:CreateNodegroup' :: CreateNodegroup -> Maybe RemoteAccessConfig
remoteAccess} -> Maybe RemoteAccessConfig
remoteAccess) (\s :: CreateNodegroup
s@CreateNodegroup' {} Maybe RemoteAccessConfig
a -> CreateNodegroup
s {$sel:remoteAccess:CreateNodegroup' :: Maybe RemoteAccessConfig
remoteAccess = Maybe RemoteAccessConfig
a} :: CreateNodegroup)

-- | The scaling configuration details for the Auto Scaling group that is
-- created for your node group.
createNodegroup_scalingConfig :: Lens.Lens' CreateNodegroup (Prelude.Maybe NodegroupScalingConfig)
createNodegroup_scalingConfig :: Lens' CreateNodegroup (Maybe NodegroupScalingConfig)
createNodegroup_scalingConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNodegroup' {Maybe NodegroupScalingConfig
scalingConfig :: Maybe NodegroupScalingConfig
$sel:scalingConfig:CreateNodegroup' :: CreateNodegroup -> Maybe NodegroupScalingConfig
scalingConfig} -> Maybe NodegroupScalingConfig
scalingConfig) (\s :: CreateNodegroup
s@CreateNodegroup' {} Maybe NodegroupScalingConfig
a -> CreateNodegroup
s {$sel:scalingConfig:CreateNodegroup' :: Maybe NodegroupScalingConfig
scalingConfig = Maybe NodegroupScalingConfig
a} :: CreateNodegroup)

-- | The metadata to apply to the node group to assist with categorization
-- and organization. Each tag consists of a key and an optional value. You
-- define both. Node group tags do not propagate to any other resources
-- associated with the node group, such as the Amazon EC2 instances or
-- subnets.
createNodegroup_tags :: Lens.Lens' CreateNodegroup (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createNodegroup_tags :: Lens' CreateNodegroup (Maybe (HashMap Text Text))
createNodegroup_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNodegroup' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateNodegroup' :: CreateNodegroup -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateNodegroup
s@CreateNodegroup' {} Maybe (HashMap Text Text)
a -> CreateNodegroup
s {$sel:tags:CreateNodegroup' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateNodegroup) 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 Kubernetes taints to be applied to the nodes in the node group. For
-- more information, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/node-taints-managed-node-groups.html Node taints on managed node groups>.
createNodegroup_taints :: Lens.Lens' CreateNodegroup (Prelude.Maybe [Taint])
createNodegroup_taints :: Lens' CreateNodegroup (Maybe [Taint])
createNodegroup_taints = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNodegroup' {Maybe [Taint]
taints :: Maybe [Taint]
$sel:taints:CreateNodegroup' :: CreateNodegroup -> Maybe [Taint]
taints} -> Maybe [Taint]
taints) (\s :: CreateNodegroup
s@CreateNodegroup' {} Maybe [Taint]
a -> CreateNodegroup
s {$sel:taints:CreateNodegroup' :: Maybe [Taint]
taints = Maybe [Taint]
a} :: CreateNodegroup) 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 node group update configuration.
createNodegroup_updateConfig :: Lens.Lens' CreateNodegroup (Prelude.Maybe NodegroupUpdateConfig)
createNodegroup_updateConfig :: Lens' CreateNodegroup (Maybe NodegroupUpdateConfig)
createNodegroup_updateConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNodegroup' {Maybe NodegroupUpdateConfig
updateConfig :: Maybe NodegroupUpdateConfig
$sel:updateConfig:CreateNodegroup' :: CreateNodegroup -> Maybe NodegroupUpdateConfig
updateConfig} -> Maybe NodegroupUpdateConfig
updateConfig) (\s :: CreateNodegroup
s@CreateNodegroup' {} Maybe NodegroupUpdateConfig
a -> CreateNodegroup
s {$sel:updateConfig:CreateNodegroup' :: Maybe NodegroupUpdateConfig
updateConfig = Maybe NodegroupUpdateConfig
a} :: CreateNodegroup)

-- | The Kubernetes version to use for your managed nodes. By default, the
-- Kubernetes version of the cluster is used, and this is the only accepted
-- specified value. If you specify @launchTemplate@, and your launch
-- template uses a custom AMI, then don\'t specify @version@, or the node
-- group deployment will fail. For more information about using launch
-- templates with Amazon EKS, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/launch-templates.html Launch template support>
-- in the /Amazon EKS User Guide/.
createNodegroup_version :: Lens.Lens' CreateNodegroup (Prelude.Maybe Prelude.Text)
createNodegroup_version :: Lens' CreateNodegroup (Maybe Text)
createNodegroup_version = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNodegroup' {Maybe Text
version :: Maybe Text
$sel:version:CreateNodegroup' :: CreateNodegroup -> Maybe Text
version} -> Maybe Text
version) (\s :: CreateNodegroup
s@CreateNodegroup' {} Maybe Text
a -> CreateNodegroup
s {$sel:version:CreateNodegroup' :: Maybe Text
version = Maybe Text
a} :: CreateNodegroup)

-- | The name of the cluster to create the node group in.
createNodegroup_clusterName :: Lens.Lens' CreateNodegroup Prelude.Text
createNodegroup_clusterName :: Lens' CreateNodegroup Text
createNodegroup_clusterName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNodegroup' {Text
clusterName :: Text
$sel:clusterName:CreateNodegroup' :: CreateNodegroup -> Text
clusterName} -> Text
clusterName) (\s :: CreateNodegroup
s@CreateNodegroup' {} Text
a -> CreateNodegroup
s {$sel:clusterName:CreateNodegroup' :: Text
clusterName = Text
a} :: CreateNodegroup)

-- | The unique name to give your node group.
createNodegroup_nodegroupName :: Lens.Lens' CreateNodegroup Prelude.Text
createNodegroup_nodegroupName :: Lens' CreateNodegroup Text
createNodegroup_nodegroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNodegroup' {Text
nodegroupName :: Text
$sel:nodegroupName:CreateNodegroup' :: CreateNodegroup -> Text
nodegroupName} -> Text
nodegroupName) (\s :: CreateNodegroup
s@CreateNodegroup' {} Text
a -> CreateNodegroup
s {$sel:nodegroupName:CreateNodegroup' :: Text
nodegroupName = Text
a} :: CreateNodegroup)

-- | The subnets to use for the Auto Scaling group that is created for your
-- node group. If you specify @launchTemplate@, then don\'t specify
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_CreateNetworkInterface.html SubnetId>
-- in your launch template, or the node group deployment will fail. For
-- more information about using launch templates with Amazon EKS, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/launch-templates.html Launch template support>
-- in the /Amazon EKS User Guide/.
createNodegroup_subnets :: Lens.Lens' CreateNodegroup [Prelude.Text]
createNodegroup_subnets :: Lens' CreateNodegroup [Text]
createNodegroup_subnets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNodegroup' {[Text]
subnets :: [Text]
$sel:subnets:CreateNodegroup' :: CreateNodegroup -> [Text]
subnets} -> [Text]
subnets) (\s :: CreateNodegroup
s@CreateNodegroup' {} [Text]
a -> CreateNodegroup
s {$sel:subnets:CreateNodegroup' :: [Text]
subnets = [Text]
a} :: CreateNodegroup) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The Amazon Resource Name (ARN) of the IAM role to associate with your
-- node group. The Amazon EKS worker node @kubelet@ daemon makes calls to
-- Amazon Web Services APIs on your behalf. Nodes receive permissions for
-- these API calls through an IAM instance profile and associated policies.
-- Before you can launch nodes and register them into a cluster, you must
-- create an IAM role for those nodes to use when they are launched. For
-- more information, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/create-node-role.html Amazon EKS node IAM role>
-- in the //Amazon EKS User Guide// . If you specify @launchTemplate@, then
-- don\'t specify
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_IamInstanceProfile.html IamInstanceProfile>
-- in your launch template, or the node group deployment will fail. For
-- more information about using launch templates with Amazon EKS, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/launch-templates.html Launch template support>
-- in the /Amazon EKS User Guide/.
createNodegroup_nodeRole :: Lens.Lens' CreateNodegroup Prelude.Text
createNodegroup_nodeRole :: Lens' CreateNodegroup Text
createNodegroup_nodeRole = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNodegroup' {Text
nodeRole :: Text
$sel:nodeRole:CreateNodegroup' :: CreateNodegroup -> Text
nodeRole} -> Text
nodeRole) (\s :: CreateNodegroup
s@CreateNodegroup' {} Text
a -> CreateNodegroup
s {$sel:nodeRole:CreateNodegroup' :: Text
nodeRole = Text
a} :: CreateNodegroup)

instance Core.AWSRequest CreateNodegroup where
  type
    AWSResponse CreateNodegroup =
      CreateNodegroupResponse
  request :: (Service -> Service) -> CreateNodegroup -> Request CreateNodegroup
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 CreateNodegroup
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateNodegroup)))
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 Nodegroup -> Int -> CreateNodegroupResponse
CreateNodegroupResponse'
            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
"nodegroup")
            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 CreateNodegroup where
  hashWithSalt :: Int -> CreateNodegroup -> Int
hashWithSalt Int
_salt CreateNodegroup' {[Text]
Maybe Int
Maybe [Text]
Maybe [Taint]
Maybe Text
Maybe (HashMap Text Text)
Maybe AMITypes
Maybe CapacityTypes
Maybe LaunchTemplateSpecification
Maybe NodegroupScalingConfig
Maybe NodegroupUpdateConfig
Maybe RemoteAccessConfig
Text
nodeRole :: Text
subnets :: [Text]
nodegroupName :: Text
clusterName :: Text
version :: Maybe Text
updateConfig :: Maybe NodegroupUpdateConfig
taints :: Maybe [Taint]
tags :: Maybe (HashMap Text Text)
scalingConfig :: Maybe NodegroupScalingConfig
remoteAccess :: Maybe RemoteAccessConfig
releaseVersion :: Maybe Text
launchTemplate :: Maybe LaunchTemplateSpecification
labels :: Maybe (HashMap Text Text)
instanceTypes :: Maybe [Text]
diskSize :: Maybe Int
clientRequestToken :: Maybe Text
capacityType :: Maybe CapacityTypes
amiType :: Maybe AMITypes
$sel:nodeRole:CreateNodegroup' :: CreateNodegroup -> Text
$sel:subnets:CreateNodegroup' :: CreateNodegroup -> [Text]
$sel:nodegroupName:CreateNodegroup' :: CreateNodegroup -> Text
$sel:clusterName:CreateNodegroup' :: CreateNodegroup -> Text
$sel:version:CreateNodegroup' :: CreateNodegroup -> Maybe Text
$sel:updateConfig:CreateNodegroup' :: CreateNodegroup -> Maybe NodegroupUpdateConfig
$sel:taints:CreateNodegroup' :: CreateNodegroup -> Maybe [Taint]
$sel:tags:CreateNodegroup' :: CreateNodegroup -> Maybe (HashMap Text Text)
$sel:scalingConfig:CreateNodegroup' :: CreateNodegroup -> Maybe NodegroupScalingConfig
$sel:remoteAccess:CreateNodegroup' :: CreateNodegroup -> Maybe RemoteAccessConfig
$sel:releaseVersion:CreateNodegroup' :: CreateNodegroup -> Maybe Text
$sel:launchTemplate:CreateNodegroup' :: CreateNodegroup -> Maybe LaunchTemplateSpecification
$sel:labels:CreateNodegroup' :: CreateNodegroup -> Maybe (HashMap Text Text)
$sel:instanceTypes:CreateNodegroup' :: CreateNodegroup -> Maybe [Text]
$sel:diskSize:CreateNodegroup' :: CreateNodegroup -> Maybe Int
$sel:clientRequestToken:CreateNodegroup' :: CreateNodegroup -> Maybe Text
$sel:capacityType:CreateNodegroup' :: CreateNodegroup -> Maybe CapacityTypes
$sel:amiType:CreateNodegroup' :: CreateNodegroup -> Maybe AMITypes
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AMITypes
amiType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CapacityTypes
capacityType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientRequestToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
diskSize
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
instanceTypes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
labels
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LaunchTemplateSpecification
launchTemplate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
releaseVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RemoteAccessConfig
remoteAccess
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe NodegroupScalingConfig
scalingConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Taint]
taints
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe NodegroupUpdateConfig
updateConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
version
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clusterName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
nodegroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
subnets
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
nodeRole

instance Prelude.NFData CreateNodegroup where
  rnf :: CreateNodegroup -> ()
rnf CreateNodegroup' {[Text]
Maybe Int
Maybe [Text]
Maybe [Taint]
Maybe Text
Maybe (HashMap Text Text)
Maybe AMITypes
Maybe CapacityTypes
Maybe LaunchTemplateSpecification
Maybe NodegroupScalingConfig
Maybe NodegroupUpdateConfig
Maybe RemoteAccessConfig
Text
nodeRole :: Text
subnets :: [Text]
nodegroupName :: Text
clusterName :: Text
version :: Maybe Text
updateConfig :: Maybe NodegroupUpdateConfig
taints :: Maybe [Taint]
tags :: Maybe (HashMap Text Text)
scalingConfig :: Maybe NodegroupScalingConfig
remoteAccess :: Maybe RemoteAccessConfig
releaseVersion :: Maybe Text
launchTemplate :: Maybe LaunchTemplateSpecification
labels :: Maybe (HashMap Text Text)
instanceTypes :: Maybe [Text]
diskSize :: Maybe Int
clientRequestToken :: Maybe Text
capacityType :: Maybe CapacityTypes
amiType :: Maybe AMITypes
$sel:nodeRole:CreateNodegroup' :: CreateNodegroup -> Text
$sel:subnets:CreateNodegroup' :: CreateNodegroup -> [Text]
$sel:nodegroupName:CreateNodegroup' :: CreateNodegroup -> Text
$sel:clusterName:CreateNodegroup' :: CreateNodegroup -> Text
$sel:version:CreateNodegroup' :: CreateNodegroup -> Maybe Text
$sel:updateConfig:CreateNodegroup' :: CreateNodegroup -> Maybe NodegroupUpdateConfig
$sel:taints:CreateNodegroup' :: CreateNodegroup -> Maybe [Taint]
$sel:tags:CreateNodegroup' :: CreateNodegroup -> Maybe (HashMap Text Text)
$sel:scalingConfig:CreateNodegroup' :: CreateNodegroup -> Maybe NodegroupScalingConfig
$sel:remoteAccess:CreateNodegroup' :: CreateNodegroup -> Maybe RemoteAccessConfig
$sel:releaseVersion:CreateNodegroup' :: CreateNodegroup -> Maybe Text
$sel:launchTemplate:CreateNodegroup' :: CreateNodegroup -> Maybe LaunchTemplateSpecification
$sel:labels:CreateNodegroup' :: CreateNodegroup -> Maybe (HashMap Text Text)
$sel:instanceTypes:CreateNodegroup' :: CreateNodegroup -> Maybe [Text]
$sel:diskSize:CreateNodegroup' :: CreateNodegroup -> Maybe Int
$sel:clientRequestToken:CreateNodegroup' :: CreateNodegroup -> Maybe Text
$sel:capacityType:CreateNodegroup' :: CreateNodegroup -> Maybe CapacityTypes
$sel:amiType:CreateNodegroup' :: CreateNodegroup -> Maybe AMITypes
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AMITypes
amiType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CapacityTypes
capacityType
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Int
diskSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
instanceTypes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
labels
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LaunchTemplateSpecification
launchTemplate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
releaseVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RemoteAccessConfig
remoteAccess
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe NodegroupScalingConfig
scalingConfig
      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 Maybe [Taint]
taints
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe NodegroupUpdateConfig
updateConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
version
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
clusterName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
nodegroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
subnets
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
nodeRole

instance Data.ToHeaders CreateNodegroup where
  toHeaders :: CreateNodegroup -> 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 CreateNodegroup where
  toJSON :: CreateNodegroup -> Value
toJSON CreateNodegroup' {[Text]
Maybe Int
Maybe [Text]
Maybe [Taint]
Maybe Text
Maybe (HashMap Text Text)
Maybe AMITypes
Maybe CapacityTypes
Maybe LaunchTemplateSpecification
Maybe NodegroupScalingConfig
Maybe NodegroupUpdateConfig
Maybe RemoteAccessConfig
Text
nodeRole :: Text
subnets :: [Text]
nodegroupName :: Text
clusterName :: Text
version :: Maybe Text
updateConfig :: Maybe NodegroupUpdateConfig
taints :: Maybe [Taint]
tags :: Maybe (HashMap Text Text)
scalingConfig :: Maybe NodegroupScalingConfig
remoteAccess :: Maybe RemoteAccessConfig
releaseVersion :: Maybe Text
launchTemplate :: Maybe LaunchTemplateSpecification
labels :: Maybe (HashMap Text Text)
instanceTypes :: Maybe [Text]
diskSize :: Maybe Int
clientRequestToken :: Maybe Text
capacityType :: Maybe CapacityTypes
amiType :: Maybe AMITypes
$sel:nodeRole:CreateNodegroup' :: CreateNodegroup -> Text
$sel:subnets:CreateNodegroup' :: CreateNodegroup -> [Text]
$sel:nodegroupName:CreateNodegroup' :: CreateNodegroup -> Text
$sel:clusterName:CreateNodegroup' :: CreateNodegroup -> Text
$sel:version:CreateNodegroup' :: CreateNodegroup -> Maybe Text
$sel:updateConfig:CreateNodegroup' :: CreateNodegroup -> Maybe NodegroupUpdateConfig
$sel:taints:CreateNodegroup' :: CreateNodegroup -> Maybe [Taint]
$sel:tags:CreateNodegroup' :: CreateNodegroup -> Maybe (HashMap Text Text)
$sel:scalingConfig:CreateNodegroup' :: CreateNodegroup -> Maybe NodegroupScalingConfig
$sel:remoteAccess:CreateNodegroup' :: CreateNodegroup -> Maybe RemoteAccessConfig
$sel:releaseVersion:CreateNodegroup' :: CreateNodegroup -> Maybe Text
$sel:launchTemplate:CreateNodegroup' :: CreateNodegroup -> Maybe LaunchTemplateSpecification
$sel:labels:CreateNodegroup' :: CreateNodegroup -> Maybe (HashMap Text Text)
$sel:instanceTypes:CreateNodegroup' :: CreateNodegroup -> Maybe [Text]
$sel:diskSize:CreateNodegroup' :: CreateNodegroup -> Maybe Int
$sel:clientRequestToken:CreateNodegroup' :: CreateNodegroup -> Maybe Text
$sel:capacityType:CreateNodegroup' :: CreateNodegroup -> Maybe CapacityTypes
$sel:amiType:CreateNodegroup' :: CreateNodegroup -> Maybe AMITypes
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"amiType" 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 AMITypes
amiType,
            (Key
"capacityType" 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 CapacityTypes
capacityType,
            (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
"diskSize" 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 Int
diskSize,
            (Key
"instanceTypes" 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]
instanceTypes,
            (Key
"labels" 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)
labels,
            (Key
"launchTemplate" 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 LaunchTemplateSpecification
launchTemplate,
            (Key
"releaseVersion" 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
releaseVersion,
            (Key
"remoteAccess" 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 RemoteAccessConfig
remoteAccess,
            (Key
"scalingConfig" 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 NodegroupScalingConfig
scalingConfig,
            (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,
            (Key
"taints" 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 [Taint]
taints,
            (Key
"updateConfig" 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 NodegroupUpdateConfig
updateConfig,
            (Key
"version" 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
version,
            forall a. a -> Maybe a
Prelude.Just (Key
"nodegroupName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
nodegroupName),
            forall a. a -> Maybe a
Prelude.Just (Key
"subnets" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [Text]
subnets),
            forall a. a -> Maybe a
Prelude.Just (Key
"nodeRole" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
nodeRole)
          ]
      )

instance Data.ToPath CreateNodegroup where
  toPath :: CreateNodegroup -> ByteString
toPath CreateNodegroup' {[Text]
Maybe Int
Maybe [Text]
Maybe [Taint]
Maybe Text
Maybe (HashMap Text Text)
Maybe AMITypes
Maybe CapacityTypes
Maybe LaunchTemplateSpecification
Maybe NodegroupScalingConfig
Maybe NodegroupUpdateConfig
Maybe RemoteAccessConfig
Text
nodeRole :: Text
subnets :: [Text]
nodegroupName :: Text
clusterName :: Text
version :: Maybe Text
updateConfig :: Maybe NodegroupUpdateConfig
taints :: Maybe [Taint]
tags :: Maybe (HashMap Text Text)
scalingConfig :: Maybe NodegroupScalingConfig
remoteAccess :: Maybe RemoteAccessConfig
releaseVersion :: Maybe Text
launchTemplate :: Maybe LaunchTemplateSpecification
labels :: Maybe (HashMap Text Text)
instanceTypes :: Maybe [Text]
diskSize :: Maybe Int
clientRequestToken :: Maybe Text
capacityType :: Maybe CapacityTypes
amiType :: Maybe AMITypes
$sel:nodeRole:CreateNodegroup' :: CreateNodegroup -> Text
$sel:subnets:CreateNodegroup' :: CreateNodegroup -> [Text]
$sel:nodegroupName:CreateNodegroup' :: CreateNodegroup -> Text
$sel:clusterName:CreateNodegroup' :: CreateNodegroup -> Text
$sel:version:CreateNodegroup' :: CreateNodegroup -> Maybe Text
$sel:updateConfig:CreateNodegroup' :: CreateNodegroup -> Maybe NodegroupUpdateConfig
$sel:taints:CreateNodegroup' :: CreateNodegroup -> Maybe [Taint]
$sel:tags:CreateNodegroup' :: CreateNodegroup -> Maybe (HashMap Text Text)
$sel:scalingConfig:CreateNodegroup' :: CreateNodegroup -> Maybe NodegroupScalingConfig
$sel:remoteAccess:CreateNodegroup' :: CreateNodegroup -> Maybe RemoteAccessConfig
$sel:releaseVersion:CreateNodegroup' :: CreateNodegroup -> Maybe Text
$sel:launchTemplate:CreateNodegroup' :: CreateNodegroup -> Maybe LaunchTemplateSpecification
$sel:labels:CreateNodegroup' :: CreateNodegroup -> Maybe (HashMap Text Text)
$sel:instanceTypes:CreateNodegroup' :: CreateNodegroup -> Maybe [Text]
$sel:diskSize:CreateNodegroup' :: CreateNodegroup -> Maybe Int
$sel:clientRequestToken:CreateNodegroup' :: CreateNodegroup -> Maybe Text
$sel:capacityType:CreateNodegroup' :: CreateNodegroup -> Maybe CapacityTypes
$sel:amiType:CreateNodegroup' :: CreateNodegroup -> Maybe AMITypes
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/clusters/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
clusterName, ByteString
"/node-groups"]

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

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

-- |
-- Create a value of 'CreateNodegroupResponse' 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:
--
-- 'nodegroup', 'createNodegroupResponse_nodegroup' - The full description of your new node group.
--
-- 'httpStatus', 'createNodegroupResponse_httpStatus' - The response's http status code.
newCreateNodegroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateNodegroupResponse
newCreateNodegroupResponse :: Int -> CreateNodegroupResponse
newCreateNodegroupResponse Int
pHttpStatus_ =
  CreateNodegroupResponse'
    { $sel:nodegroup:CreateNodegroupResponse' :: Maybe Nodegroup
nodegroup =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateNodegroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The full description of your new node group.
createNodegroupResponse_nodegroup :: Lens.Lens' CreateNodegroupResponse (Prelude.Maybe Nodegroup)
createNodegroupResponse_nodegroup :: Lens' CreateNodegroupResponse (Maybe Nodegroup)
createNodegroupResponse_nodegroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNodegroupResponse' {Maybe Nodegroup
nodegroup :: Maybe Nodegroup
$sel:nodegroup:CreateNodegroupResponse' :: CreateNodegroupResponse -> Maybe Nodegroup
nodegroup} -> Maybe Nodegroup
nodegroup) (\s :: CreateNodegroupResponse
s@CreateNodegroupResponse' {} Maybe Nodegroup
a -> CreateNodegroupResponse
s {$sel:nodegroup:CreateNodegroupResponse' :: Maybe Nodegroup
nodegroup = Maybe Nodegroup
a} :: CreateNodegroupResponse)

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

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