{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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.Types.VpcConfigRequest
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.EKS.Types.VpcConfigRequest where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

-- | An object representing the VPC configuration to use for an Amazon EKS
-- cluster.
--
-- /See:/ 'newVpcConfigRequest' smart constructor.
data VpcConfigRequest = VpcConfigRequest'
  { -- | Set this value to @true@ to enable private access for your cluster\'s
    -- Kubernetes API server endpoint. If you enable private access, Kubernetes
    -- API requests from within your cluster\'s VPC use the private VPC
    -- endpoint. The default value for this parameter is @false@, which
    -- disables private access for your Kubernetes API server. If you disable
    -- private access and you have nodes or Fargate pods in the cluster, then
    -- ensure that @publicAccessCidrs@ includes the necessary CIDR blocks for
    -- communication with the nodes or Fargate pods. For more information, see
    -- <https://docs.aws.amazon.com/eks/latest/userguide/cluster-endpoint.html Amazon EKS cluster endpoint access control>
    -- in the //Amazon EKS User Guide// .
    VpcConfigRequest -> Maybe Bool
endpointPrivateAccess :: Prelude.Maybe Prelude.Bool,
    -- | Set this value to @false@ to disable public access to your cluster\'s
    -- Kubernetes API server endpoint. If you disable public access, your
    -- cluster\'s Kubernetes API server can only receive requests from within
    -- the cluster VPC. The default value for this parameter is @true@, which
    -- enables public access for your Kubernetes API server. For more
    -- information, see
    -- <https://docs.aws.amazon.com/eks/latest/userguide/cluster-endpoint.html Amazon EKS cluster endpoint access control>
    -- in the //Amazon EKS User Guide// .
    VpcConfigRequest -> Maybe Bool
endpointPublicAccess :: Prelude.Maybe Prelude.Bool,
    -- | The CIDR blocks that are allowed access to your cluster\'s public
    -- Kubernetes API server endpoint. Communication to the endpoint from
    -- addresses outside of the CIDR blocks that you specify is denied. The
    -- default value is @0.0.0.0\/0@. If you\'ve disabled private endpoint
    -- access and you have nodes or Fargate pods in the cluster, then ensure
    -- that you specify the necessary CIDR blocks. For more information, see
    -- <https://docs.aws.amazon.com/eks/latest/userguide/cluster-endpoint.html Amazon EKS cluster endpoint access control>
    -- in the //Amazon EKS User Guide// .
    VpcConfigRequest -> Maybe [Text]
publicAccessCidrs :: Prelude.Maybe [Prelude.Text],
    -- | Specify one or more security groups for the cross-account elastic
    -- network interfaces that Amazon EKS creates to use that allow
    -- communication between your nodes and the Kubernetes control plane. If
    -- you don\'t specify any security groups, then familiarize yourself with
    -- the difference between Amazon EKS defaults for clusters deployed with
    -- Kubernetes. For more information, see
    -- <https://docs.aws.amazon.com/eks/latest/userguide/sec-group-reqs.html Amazon EKS security group considerations>
    -- in the //Amazon EKS User Guide// .
    VpcConfigRequest -> Maybe [Text]
securityGroupIds :: Prelude.Maybe [Prelude.Text],
    -- | Specify subnets for your Amazon EKS nodes. Amazon EKS creates
    -- cross-account elastic network interfaces in these subnets to allow
    -- communication between your nodes and the Kubernetes control plane.
    VpcConfigRequest -> Maybe [Text]
subnetIds :: Prelude.Maybe [Prelude.Text]
  }
  deriving (VpcConfigRequest -> VpcConfigRequest -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VpcConfigRequest -> VpcConfigRequest -> Bool
$c/= :: VpcConfigRequest -> VpcConfigRequest -> Bool
== :: VpcConfigRequest -> VpcConfigRequest -> Bool
$c== :: VpcConfigRequest -> VpcConfigRequest -> Bool
Prelude.Eq, ReadPrec [VpcConfigRequest]
ReadPrec VpcConfigRequest
Int -> ReadS VpcConfigRequest
ReadS [VpcConfigRequest]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VpcConfigRequest]
$creadListPrec :: ReadPrec [VpcConfigRequest]
readPrec :: ReadPrec VpcConfigRequest
$creadPrec :: ReadPrec VpcConfigRequest
readList :: ReadS [VpcConfigRequest]
$creadList :: ReadS [VpcConfigRequest]
readsPrec :: Int -> ReadS VpcConfigRequest
$creadsPrec :: Int -> ReadS VpcConfigRequest
Prelude.Read, Int -> VpcConfigRequest -> ShowS
[VpcConfigRequest] -> ShowS
VpcConfigRequest -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VpcConfigRequest] -> ShowS
$cshowList :: [VpcConfigRequest] -> ShowS
show :: VpcConfigRequest -> String
$cshow :: VpcConfigRequest -> String
showsPrec :: Int -> VpcConfigRequest -> ShowS
$cshowsPrec :: Int -> VpcConfigRequest -> ShowS
Prelude.Show, forall x. Rep VpcConfigRequest x -> VpcConfigRequest
forall x. VpcConfigRequest -> Rep VpcConfigRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VpcConfigRequest x -> VpcConfigRequest
$cfrom :: forall x. VpcConfigRequest -> Rep VpcConfigRequest x
Prelude.Generic)

-- |
-- Create a value of 'VpcConfigRequest' 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:
--
-- 'endpointPrivateAccess', 'vpcConfigRequest_endpointPrivateAccess' - Set this value to @true@ to enable private access for your cluster\'s
-- Kubernetes API server endpoint. If you enable private access, Kubernetes
-- API requests from within your cluster\'s VPC use the private VPC
-- endpoint. The default value for this parameter is @false@, which
-- disables private access for your Kubernetes API server. If you disable
-- private access and you have nodes or Fargate pods in the cluster, then
-- ensure that @publicAccessCidrs@ includes the necessary CIDR blocks for
-- communication with the nodes or Fargate pods. For more information, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/cluster-endpoint.html Amazon EKS cluster endpoint access control>
-- in the //Amazon EKS User Guide// .
--
-- 'endpointPublicAccess', 'vpcConfigRequest_endpointPublicAccess' - Set this value to @false@ to disable public access to your cluster\'s
-- Kubernetes API server endpoint. If you disable public access, your
-- cluster\'s Kubernetes API server can only receive requests from within
-- the cluster VPC. The default value for this parameter is @true@, which
-- enables public access for your Kubernetes API server. For more
-- information, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/cluster-endpoint.html Amazon EKS cluster endpoint access control>
-- in the //Amazon EKS User Guide// .
--
-- 'publicAccessCidrs', 'vpcConfigRequest_publicAccessCidrs' - The CIDR blocks that are allowed access to your cluster\'s public
-- Kubernetes API server endpoint. Communication to the endpoint from
-- addresses outside of the CIDR blocks that you specify is denied. The
-- default value is @0.0.0.0\/0@. If you\'ve disabled private endpoint
-- access and you have nodes or Fargate pods in the cluster, then ensure
-- that you specify the necessary CIDR blocks. For more information, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/cluster-endpoint.html Amazon EKS cluster endpoint access control>
-- in the //Amazon EKS User Guide// .
--
-- 'securityGroupIds', 'vpcConfigRequest_securityGroupIds' - Specify one or more security groups for the cross-account elastic
-- network interfaces that Amazon EKS creates to use that allow
-- communication between your nodes and the Kubernetes control plane. If
-- you don\'t specify any security groups, then familiarize yourself with
-- the difference between Amazon EKS defaults for clusters deployed with
-- Kubernetes. For more information, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/sec-group-reqs.html Amazon EKS security group considerations>
-- in the //Amazon EKS User Guide// .
--
-- 'subnetIds', 'vpcConfigRequest_subnetIds' - Specify subnets for your Amazon EKS nodes. Amazon EKS creates
-- cross-account elastic network interfaces in these subnets to allow
-- communication between your nodes and the Kubernetes control plane.
newVpcConfigRequest ::
  VpcConfigRequest
newVpcConfigRequest :: VpcConfigRequest
newVpcConfigRequest =
  VpcConfigRequest'
    { $sel:endpointPrivateAccess:VpcConfigRequest' :: Maybe Bool
endpointPrivateAccess =
        forall a. Maybe a
Prelude.Nothing,
      $sel:endpointPublicAccess:VpcConfigRequest' :: Maybe Bool
endpointPublicAccess = forall a. Maybe a
Prelude.Nothing,
      $sel:publicAccessCidrs:VpcConfigRequest' :: Maybe [Text]
publicAccessCidrs = forall a. Maybe a
Prelude.Nothing,
      $sel:securityGroupIds:VpcConfigRequest' :: Maybe [Text]
securityGroupIds = forall a. Maybe a
Prelude.Nothing,
      $sel:subnetIds:VpcConfigRequest' :: Maybe [Text]
subnetIds = forall a. Maybe a
Prelude.Nothing
    }

-- | Set this value to @true@ to enable private access for your cluster\'s
-- Kubernetes API server endpoint. If you enable private access, Kubernetes
-- API requests from within your cluster\'s VPC use the private VPC
-- endpoint. The default value for this parameter is @false@, which
-- disables private access for your Kubernetes API server. If you disable
-- private access and you have nodes or Fargate pods in the cluster, then
-- ensure that @publicAccessCidrs@ includes the necessary CIDR blocks for
-- communication with the nodes or Fargate pods. For more information, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/cluster-endpoint.html Amazon EKS cluster endpoint access control>
-- in the //Amazon EKS User Guide// .
vpcConfigRequest_endpointPrivateAccess :: Lens.Lens' VpcConfigRequest (Prelude.Maybe Prelude.Bool)
vpcConfigRequest_endpointPrivateAccess :: Lens' VpcConfigRequest (Maybe Bool)
vpcConfigRequest_endpointPrivateAccess = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VpcConfigRequest' {Maybe Bool
endpointPrivateAccess :: Maybe Bool
$sel:endpointPrivateAccess:VpcConfigRequest' :: VpcConfigRequest -> Maybe Bool
endpointPrivateAccess} -> Maybe Bool
endpointPrivateAccess) (\s :: VpcConfigRequest
s@VpcConfigRequest' {} Maybe Bool
a -> VpcConfigRequest
s {$sel:endpointPrivateAccess:VpcConfigRequest' :: Maybe Bool
endpointPrivateAccess = Maybe Bool
a} :: VpcConfigRequest)

-- | Set this value to @false@ to disable public access to your cluster\'s
-- Kubernetes API server endpoint. If you disable public access, your
-- cluster\'s Kubernetes API server can only receive requests from within
-- the cluster VPC. The default value for this parameter is @true@, which
-- enables public access for your Kubernetes API server. For more
-- information, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/cluster-endpoint.html Amazon EKS cluster endpoint access control>
-- in the //Amazon EKS User Guide// .
vpcConfigRequest_endpointPublicAccess :: Lens.Lens' VpcConfigRequest (Prelude.Maybe Prelude.Bool)
vpcConfigRequest_endpointPublicAccess :: Lens' VpcConfigRequest (Maybe Bool)
vpcConfigRequest_endpointPublicAccess = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VpcConfigRequest' {Maybe Bool
endpointPublicAccess :: Maybe Bool
$sel:endpointPublicAccess:VpcConfigRequest' :: VpcConfigRequest -> Maybe Bool
endpointPublicAccess} -> Maybe Bool
endpointPublicAccess) (\s :: VpcConfigRequest
s@VpcConfigRequest' {} Maybe Bool
a -> VpcConfigRequest
s {$sel:endpointPublicAccess:VpcConfigRequest' :: Maybe Bool
endpointPublicAccess = Maybe Bool
a} :: VpcConfigRequest)

-- | The CIDR blocks that are allowed access to your cluster\'s public
-- Kubernetes API server endpoint. Communication to the endpoint from
-- addresses outside of the CIDR blocks that you specify is denied. The
-- default value is @0.0.0.0\/0@. If you\'ve disabled private endpoint
-- access and you have nodes or Fargate pods in the cluster, then ensure
-- that you specify the necessary CIDR blocks. For more information, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/cluster-endpoint.html Amazon EKS cluster endpoint access control>
-- in the //Amazon EKS User Guide// .
vpcConfigRequest_publicAccessCidrs :: Lens.Lens' VpcConfigRequest (Prelude.Maybe [Prelude.Text])
vpcConfigRequest_publicAccessCidrs :: Lens' VpcConfigRequest (Maybe [Text])
vpcConfigRequest_publicAccessCidrs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VpcConfigRequest' {Maybe [Text]
publicAccessCidrs :: Maybe [Text]
$sel:publicAccessCidrs:VpcConfigRequest' :: VpcConfigRequest -> Maybe [Text]
publicAccessCidrs} -> Maybe [Text]
publicAccessCidrs) (\s :: VpcConfigRequest
s@VpcConfigRequest' {} Maybe [Text]
a -> VpcConfigRequest
s {$sel:publicAccessCidrs:VpcConfigRequest' :: Maybe [Text]
publicAccessCidrs = Maybe [Text]
a} :: VpcConfigRequest) 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

-- | Specify one or more security groups for the cross-account elastic
-- network interfaces that Amazon EKS creates to use that allow
-- communication between your nodes and the Kubernetes control plane. If
-- you don\'t specify any security groups, then familiarize yourself with
-- the difference between Amazon EKS defaults for clusters deployed with
-- Kubernetes. For more information, see
-- <https://docs.aws.amazon.com/eks/latest/userguide/sec-group-reqs.html Amazon EKS security group considerations>
-- in the //Amazon EKS User Guide// .
vpcConfigRequest_securityGroupIds :: Lens.Lens' VpcConfigRequest (Prelude.Maybe [Prelude.Text])
vpcConfigRequest_securityGroupIds :: Lens' VpcConfigRequest (Maybe [Text])
vpcConfigRequest_securityGroupIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VpcConfigRequest' {Maybe [Text]
securityGroupIds :: Maybe [Text]
$sel:securityGroupIds:VpcConfigRequest' :: VpcConfigRequest -> Maybe [Text]
securityGroupIds} -> Maybe [Text]
securityGroupIds) (\s :: VpcConfigRequest
s@VpcConfigRequest' {} Maybe [Text]
a -> VpcConfigRequest
s {$sel:securityGroupIds:VpcConfigRequest' :: Maybe [Text]
securityGroupIds = Maybe [Text]
a} :: VpcConfigRequest) 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

-- | Specify subnets for your Amazon EKS nodes. Amazon EKS creates
-- cross-account elastic network interfaces in these subnets to allow
-- communication between your nodes and the Kubernetes control plane.
vpcConfigRequest_subnetIds :: Lens.Lens' VpcConfigRequest (Prelude.Maybe [Prelude.Text])
vpcConfigRequest_subnetIds :: Lens' VpcConfigRequest (Maybe [Text])
vpcConfigRequest_subnetIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VpcConfigRequest' {Maybe [Text]
subnetIds :: Maybe [Text]
$sel:subnetIds:VpcConfigRequest' :: VpcConfigRequest -> Maybe [Text]
subnetIds} -> Maybe [Text]
subnetIds) (\s :: VpcConfigRequest
s@VpcConfigRequest' {} Maybe [Text]
a -> VpcConfigRequest
s {$sel:subnetIds:VpcConfigRequest' :: Maybe [Text]
subnetIds = Maybe [Text]
a} :: VpcConfigRequest) 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

instance Prelude.Hashable VpcConfigRequest where
  hashWithSalt :: Int -> VpcConfigRequest -> Int
hashWithSalt Int
_salt VpcConfigRequest' {Maybe Bool
Maybe [Text]
subnetIds :: Maybe [Text]
securityGroupIds :: Maybe [Text]
publicAccessCidrs :: Maybe [Text]
endpointPublicAccess :: Maybe Bool
endpointPrivateAccess :: Maybe Bool
$sel:subnetIds:VpcConfigRequest' :: VpcConfigRequest -> Maybe [Text]
$sel:securityGroupIds:VpcConfigRequest' :: VpcConfigRequest -> Maybe [Text]
$sel:publicAccessCidrs:VpcConfigRequest' :: VpcConfigRequest -> Maybe [Text]
$sel:endpointPublicAccess:VpcConfigRequest' :: VpcConfigRequest -> Maybe Bool
$sel:endpointPrivateAccess:VpcConfigRequest' :: VpcConfigRequest -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
endpointPrivateAccess
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
endpointPublicAccess
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
publicAccessCidrs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
securityGroupIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
subnetIds

instance Prelude.NFData VpcConfigRequest where
  rnf :: VpcConfigRequest -> ()
rnf VpcConfigRequest' {Maybe Bool
Maybe [Text]
subnetIds :: Maybe [Text]
securityGroupIds :: Maybe [Text]
publicAccessCidrs :: Maybe [Text]
endpointPublicAccess :: Maybe Bool
endpointPrivateAccess :: Maybe Bool
$sel:subnetIds:VpcConfigRequest' :: VpcConfigRequest -> Maybe [Text]
$sel:securityGroupIds:VpcConfigRequest' :: VpcConfigRequest -> Maybe [Text]
$sel:publicAccessCidrs:VpcConfigRequest' :: VpcConfigRequest -> Maybe [Text]
$sel:endpointPublicAccess:VpcConfigRequest' :: VpcConfigRequest -> Maybe Bool
$sel:endpointPrivateAccess:VpcConfigRequest' :: VpcConfigRequest -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
endpointPrivateAccess
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
endpointPublicAccess
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
publicAccessCidrs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
securityGroupIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
subnetIds

instance Data.ToJSON VpcConfigRequest where
  toJSON :: VpcConfigRequest -> Value
toJSON VpcConfigRequest' {Maybe Bool
Maybe [Text]
subnetIds :: Maybe [Text]
securityGroupIds :: Maybe [Text]
publicAccessCidrs :: Maybe [Text]
endpointPublicAccess :: Maybe Bool
endpointPrivateAccess :: Maybe Bool
$sel:subnetIds:VpcConfigRequest' :: VpcConfigRequest -> Maybe [Text]
$sel:securityGroupIds:VpcConfigRequest' :: VpcConfigRequest -> Maybe [Text]
$sel:publicAccessCidrs:VpcConfigRequest' :: VpcConfigRequest -> Maybe [Text]
$sel:endpointPublicAccess:VpcConfigRequest' :: VpcConfigRequest -> Maybe Bool
$sel:endpointPrivateAccess:VpcConfigRequest' :: VpcConfigRequest -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"endpointPrivateAccess" 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 Bool
endpointPrivateAccess,
            (Key
"endpointPublicAccess" 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 Bool
endpointPublicAccess,
            (Key
"publicAccessCidrs" 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]
publicAccessCidrs,
            (Key
"securityGroupIds" 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]
securityGroupIds,
            (Key
"subnetIds" 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]
subnetIds
          ]
      )