{-# 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.Redshift.AuthorizeClusterSecurityGroupIngress
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Adds an inbound (ingress) rule to an Amazon Redshift security group.
-- Depending on whether the application accessing your cluster is running
-- on the Internet or an Amazon EC2 instance, you can authorize inbound
-- access to either a Classless Interdomain Routing (CIDR)\/Internet
-- Protocol (IP) range or to an Amazon EC2 security group. You can add as
-- many as 20 ingress rules to an Amazon Redshift security group.
--
-- If you authorize access to an Amazon EC2 security group, specify
-- /EC2SecurityGroupName/ and /EC2SecurityGroupOwnerId/. The Amazon EC2
-- security group and Amazon Redshift cluster must be in the same Amazon
-- Web Services Region.
--
-- If you authorize access to a CIDR\/IP address range, specify /CIDRIP/.
-- For an overview of CIDR blocks, see the Wikipedia article on
-- <http://en.wikipedia.org/wiki/Classless_Inter-Domain_Routing Classless Inter-Domain Routing>.
--
-- You must also associate the security group with a cluster so that
-- clients running on these IP addresses or the EC2 instance are authorized
-- to connect to the cluster. For information about managing security
-- groups, go to
-- <https://docs.aws.amazon.com/redshift/latest/mgmt/working-with-security-groups.html Working with Security Groups>
-- in the /Amazon Redshift Cluster Management Guide/.
module Amazonka.Redshift.AuthorizeClusterSecurityGroupIngress
  ( -- * Creating a Request
    AuthorizeClusterSecurityGroupIngress (..),
    newAuthorizeClusterSecurityGroupIngress,

    -- * Request Lenses
    authorizeClusterSecurityGroupIngress_cidrip,
    authorizeClusterSecurityGroupIngress_eC2SecurityGroupName,
    authorizeClusterSecurityGroupIngress_eC2SecurityGroupOwnerId,
    authorizeClusterSecurityGroupIngress_clusterSecurityGroupName,

    -- * Destructuring the Response
    AuthorizeClusterSecurityGroupIngressResponse (..),
    newAuthorizeClusterSecurityGroupIngressResponse,

    -- * Response Lenses
    authorizeClusterSecurityGroupIngressResponse_clusterSecurityGroup,
    authorizeClusterSecurityGroupIngressResponse_httpStatus,
  )
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
import Amazonka.Redshift.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- |
--
-- /See:/ 'newAuthorizeClusterSecurityGroupIngress' smart constructor.
data AuthorizeClusterSecurityGroupIngress = AuthorizeClusterSecurityGroupIngress'
  { -- | The IP range to be added the Amazon Redshift security group.
    AuthorizeClusterSecurityGroupIngress -> Maybe Text
cidrip :: Prelude.Maybe Prelude.Text,
    -- | The EC2 security group to be added the Amazon Redshift security group.
    AuthorizeClusterSecurityGroupIngress -> Maybe Text
eC2SecurityGroupName :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services account number of the owner of the security
    -- group specified by the /EC2SecurityGroupName/ parameter. The Amazon Web
    -- Services Access Key ID is not an acceptable value.
    --
    -- Example: @111122223333@
    AuthorizeClusterSecurityGroupIngress -> Maybe Text
eC2SecurityGroupOwnerId :: Prelude.Maybe Prelude.Text,
    -- | The name of the security group to which the ingress rule is added.
    AuthorizeClusterSecurityGroupIngress -> Text
clusterSecurityGroupName :: Prelude.Text
  }
  deriving (AuthorizeClusterSecurityGroupIngress
-> AuthorizeClusterSecurityGroupIngress -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AuthorizeClusterSecurityGroupIngress
-> AuthorizeClusterSecurityGroupIngress -> Bool
$c/= :: AuthorizeClusterSecurityGroupIngress
-> AuthorizeClusterSecurityGroupIngress -> Bool
== :: AuthorizeClusterSecurityGroupIngress
-> AuthorizeClusterSecurityGroupIngress -> Bool
$c== :: AuthorizeClusterSecurityGroupIngress
-> AuthorizeClusterSecurityGroupIngress -> Bool
Prelude.Eq, ReadPrec [AuthorizeClusterSecurityGroupIngress]
ReadPrec AuthorizeClusterSecurityGroupIngress
Int -> ReadS AuthorizeClusterSecurityGroupIngress
ReadS [AuthorizeClusterSecurityGroupIngress]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AuthorizeClusterSecurityGroupIngress]
$creadListPrec :: ReadPrec [AuthorizeClusterSecurityGroupIngress]
readPrec :: ReadPrec AuthorizeClusterSecurityGroupIngress
$creadPrec :: ReadPrec AuthorizeClusterSecurityGroupIngress
readList :: ReadS [AuthorizeClusterSecurityGroupIngress]
$creadList :: ReadS [AuthorizeClusterSecurityGroupIngress]
readsPrec :: Int -> ReadS AuthorizeClusterSecurityGroupIngress
$creadsPrec :: Int -> ReadS AuthorizeClusterSecurityGroupIngress
Prelude.Read, Int -> AuthorizeClusterSecurityGroupIngress -> ShowS
[AuthorizeClusterSecurityGroupIngress] -> ShowS
AuthorizeClusterSecurityGroupIngress -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AuthorizeClusterSecurityGroupIngress] -> ShowS
$cshowList :: [AuthorizeClusterSecurityGroupIngress] -> ShowS
show :: AuthorizeClusterSecurityGroupIngress -> String
$cshow :: AuthorizeClusterSecurityGroupIngress -> String
showsPrec :: Int -> AuthorizeClusterSecurityGroupIngress -> ShowS
$cshowsPrec :: Int -> AuthorizeClusterSecurityGroupIngress -> ShowS
Prelude.Show, forall x.
Rep AuthorizeClusterSecurityGroupIngress x
-> AuthorizeClusterSecurityGroupIngress
forall x.
AuthorizeClusterSecurityGroupIngress
-> Rep AuthorizeClusterSecurityGroupIngress x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AuthorizeClusterSecurityGroupIngress x
-> AuthorizeClusterSecurityGroupIngress
$cfrom :: forall x.
AuthorizeClusterSecurityGroupIngress
-> Rep AuthorizeClusterSecurityGroupIngress x
Prelude.Generic)

-- |
-- Create a value of 'AuthorizeClusterSecurityGroupIngress' 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:
--
-- 'cidrip', 'authorizeClusterSecurityGroupIngress_cidrip' - The IP range to be added the Amazon Redshift security group.
--
-- 'eC2SecurityGroupName', 'authorizeClusterSecurityGroupIngress_eC2SecurityGroupName' - The EC2 security group to be added the Amazon Redshift security group.
--
-- 'eC2SecurityGroupOwnerId', 'authorizeClusterSecurityGroupIngress_eC2SecurityGroupOwnerId' - The Amazon Web Services account number of the owner of the security
-- group specified by the /EC2SecurityGroupName/ parameter. The Amazon Web
-- Services Access Key ID is not an acceptable value.
--
-- Example: @111122223333@
--
-- 'clusterSecurityGroupName', 'authorizeClusterSecurityGroupIngress_clusterSecurityGroupName' - The name of the security group to which the ingress rule is added.
newAuthorizeClusterSecurityGroupIngress ::
  -- | 'clusterSecurityGroupName'
  Prelude.Text ->
  AuthorizeClusterSecurityGroupIngress
newAuthorizeClusterSecurityGroupIngress :: Text -> AuthorizeClusterSecurityGroupIngress
newAuthorizeClusterSecurityGroupIngress
  Text
pClusterSecurityGroupName_ =
    AuthorizeClusterSecurityGroupIngress'
      { $sel:cidrip:AuthorizeClusterSecurityGroupIngress' :: Maybe Text
cidrip =
          forall a. Maybe a
Prelude.Nothing,
        $sel:eC2SecurityGroupName:AuthorizeClusterSecurityGroupIngress' :: Maybe Text
eC2SecurityGroupName =
          forall a. Maybe a
Prelude.Nothing,
        $sel:eC2SecurityGroupOwnerId:AuthorizeClusterSecurityGroupIngress' :: Maybe Text
eC2SecurityGroupOwnerId =
          forall a. Maybe a
Prelude.Nothing,
        $sel:clusterSecurityGroupName:AuthorizeClusterSecurityGroupIngress' :: Text
clusterSecurityGroupName =
          Text
pClusterSecurityGroupName_
      }

-- | The IP range to be added the Amazon Redshift security group.
authorizeClusterSecurityGroupIngress_cidrip :: Lens.Lens' AuthorizeClusterSecurityGroupIngress (Prelude.Maybe Prelude.Text)
authorizeClusterSecurityGroupIngress_cidrip :: Lens' AuthorizeClusterSecurityGroupIngress (Maybe Text)
authorizeClusterSecurityGroupIngress_cidrip = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AuthorizeClusterSecurityGroupIngress' {Maybe Text
cidrip :: Maybe Text
$sel:cidrip:AuthorizeClusterSecurityGroupIngress' :: AuthorizeClusterSecurityGroupIngress -> Maybe Text
cidrip} -> Maybe Text
cidrip) (\s :: AuthorizeClusterSecurityGroupIngress
s@AuthorizeClusterSecurityGroupIngress' {} Maybe Text
a -> AuthorizeClusterSecurityGroupIngress
s {$sel:cidrip:AuthorizeClusterSecurityGroupIngress' :: Maybe Text
cidrip = Maybe Text
a} :: AuthorizeClusterSecurityGroupIngress)

-- | The EC2 security group to be added the Amazon Redshift security group.
authorizeClusterSecurityGroupIngress_eC2SecurityGroupName :: Lens.Lens' AuthorizeClusterSecurityGroupIngress (Prelude.Maybe Prelude.Text)
authorizeClusterSecurityGroupIngress_eC2SecurityGroupName :: Lens' AuthorizeClusterSecurityGroupIngress (Maybe Text)
authorizeClusterSecurityGroupIngress_eC2SecurityGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AuthorizeClusterSecurityGroupIngress' {Maybe Text
eC2SecurityGroupName :: Maybe Text
$sel:eC2SecurityGroupName:AuthorizeClusterSecurityGroupIngress' :: AuthorizeClusterSecurityGroupIngress -> Maybe Text
eC2SecurityGroupName} -> Maybe Text
eC2SecurityGroupName) (\s :: AuthorizeClusterSecurityGroupIngress
s@AuthorizeClusterSecurityGroupIngress' {} Maybe Text
a -> AuthorizeClusterSecurityGroupIngress
s {$sel:eC2SecurityGroupName:AuthorizeClusterSecurityGroupIngress' :: Maybe Text
eC2SecurityGroupName = Maybe Text
a} :: AuthorizeClusterSecurityGroupIngress)

-- | The Amazon Web Services account number of the owner of the security
-- group specified by the /EC2SecurityGroupName/ parameter. The Amazon Web
-- Services Access Key ID is not an acceptable value.
--
-- Example: @111122223333@
authorizeClusterSecurityGroupIngress_eC2SecurityGroupOwnerId :: Lens.Lens' AuthorizeClusterSecurityGroupIngress (Prelude.Maybe Prelude.Text)
authorizeClusterSecurityGroupIngress_eC2SecurityGroupOwnerId :: Lens' AuthorizeClusterSecurityGroupIngress (Maybe Text)
authorizeClusterSecurityGroupIngress_eC2SecurityGroupOwnerId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AuthorizeClusterSecurityGroupIngress' {Maybe Text
eC2SecurityGroupOwnerId :: Maybe Text
$sel:eC2SecurityGroupOwnerId:AuthorizeClusterSecurityGroupIngress' :: AuthorizeClusterSecurityGroupIngress -> Maybe Text
eC2SecurityGroupOwnerId} -> Maybe Text
eC2SecurityGroupOwnerId) (\s :: AuthorizeClusterSecurityGroupIngress
s@AuthorizeClusterSecurityGroupIngress' {} Maybe Text
a -> AuthorizeClusterSecurityGroupIngress
s {$sel:eC2SecurityGroupOwnerId:AuthorizeClusterSecurityGroupIngress' :: Maybe Text
eC2SecurityGroupOwnerId = Maybe Text
a} :: AuthorizeClusterSecurityGroupIngress)

-- | The name of the security group to which the ingress rule is added.
authorizeClusterSecurityGroupIngress_clusterSecurityGroupName :: Lens.Lens' AuthorizeClusterSecurityGroupIngress Prelude.Text
authorizeClusterSecurityGroupIngress_clusterSecurityGroupName :: Lens' AuthorizeClusterSecurityGroupIngress Text
authorizeClusterSecurityGroupIngress_clusterSecurityGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AuthorizeClusterSecurityGroupIngress' {Text
clusterSecurityGroupName :: Text
$sel:clusterSecurityGroupName:AuthorizeClusterSecurityGroupIngress' :: AuthorizeClusterSecurityGroupIngress -> Text
clusterSecurityGroupName} -> Text
clusterSecurityGroupName) (\s :: AuthorizeClusterSecurityGroupIngress
s@AuthorizeClusterSecurityGroupIngress' {} Text
a -> AuthorizeClusterSecurityGroupIngress
s {$sel:clusterSecurityGroupName:AuthorizeClusterSecurityGroupIngress' :: Text
clusterSecurityGroupName = Text
a} :: AuthorizeClusterSecurityGroupIngress)

instance
  Core.AWSRequest
    AuthorizeClusterSecurityGroupIngress
  where
  type
    AWSResponse AuthorizeClusterSecurityGroupIngress =
      AuthorizeClusterSecurityGroupIngressResponse
  request :: (Service -> Service)
-> AuthorizeClusterSecurityGroupIngress
-> Request AuthorizeClusterSecurityGroupIngress
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy AuthorizeClusterSecurityGroupIngress
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse AuthorizeClusterSecurityGroupIngress)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"AuthorizeClusterSecurityGroupIngressResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe ClusterSecurityGroup
-> Int -> AuthorizeClusterSecurityGroupIngressResponse
AuthorizeClusterSecurityGroupIngressResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ClusterSecurityGroup")
            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
    AuthorizeClusterSecurityGroupIngress
  where
  hashWithSalt :: Int -> AuthorizeClusterSecurityGroupIngress -> Int
hashWithSalt
    Int
_salt
    AuthorizeClusterSecurityGroupIngress' {Maybe Text
Text
clusterSecurityGroupName :: Text
eC2SecurityGroupOwnerId :: Maybe Text
eC2SecurityGroupName :: Maybe Text
cidrip :: Maybe Text
$sel:clusterSecurityGroupName:AuthorizeClusterSecurityGroupIngress' :: AuthorizeClusterSecurityGroupIngress -> Text
$sel:eC2SecurityGroupOwnerId:AuthorizeClusterSecurityGroupIngress' :: AuthorizeClusterSecurityGroupIngress -> Maybe Text
$sel:eC2SecurityGroupName:AuthorizeClusterSecurityGroupIngress' :: AuthorizeClusterSecurityGroupIngress -> Maybe Text
$sel:cidrip:AuthorizeClusterSecurityGroupIngress' :: AuthorizeClusterSecurityGroupIngress -> Maybe Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
cidrip
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
eC2SecurityGroupName
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
eC2SecurityGroupOwnerId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clusterSecurityGroupName

instance
  Prelude.NFData
    AuthorizeClusterSecurityGroupIngress
  where
  rnf :: AuthorizeClusterSecurityGroupIngress -> ()
rnf AuthorizeClusterSecurityGroupIngress' {Maybe Text
Text
clusterSecurityGroupName :: Text
eC2SecurityGroupOwnerId :: Maybe Text
eC2SecurityGroupName :: Maybe Text
cidrip :: Maybe Text
$sel:clusterSecurityGroupName:AuthorizeClusterSecurityGroupIngress' :: AuthorizeClusterSecurityGroupIngress -> Text
$sel:eC2SecurityGroupOwnerId:AuthorizeClusterSecurityGroupIngress' :: AuthorizeClusterSecurityGroupIngress -> Maybe Text
$sel:eC2SecurityGroupName:AuthorizeClusterSecurityGroupIngress' :: AuthorizeClusterSecurityGroupIngress -> Maybe Text
$sel:cidrip:AuthorizeClusterSecurityGroupIngress' :: AuthorizeClusterSecurityGroupIngress -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
cidrip
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
eC2SecurityGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
eC2SecurityGroupOwnerId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
clusterSecurityGroupName

instance
  Data.ToHeaders
    AuthorizeClusterSecurityGroupIngress
  where
  toHeaders :: AuthorizeClusterSecurityGroupIngress -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance
  Data.ToQuery
    AuthorizeClusterSecurityGroupIngress
  where
  toQuery :: AuthorizeClusterSecurityGroupIngress -> QueryString
toQuery AuthorizeClusterSecurityGroupIngress' {Maybe Text
Text
clusterSecurityGroupName :: Text
eC2SecurityGroupOwnerId :: Maybe Text
eC2SecurityGroupName :: Maybe Text
cidrip :: Maybe Text
$sel:clusterSecurityGroupName:AuthorizeClusterSecurityGroupIngress' :: AuthorizeClusterSecurityGroupIngress -> Text
$sel:eC2SecurityGroupOwnerId:AuthorizeClusterSecurityGroupIngress' :: AuthorizeClusterSecurityGroupIngress -> Maybe Text
$sel:eC2SecurityGroupName:AuthorizeClusterSecurityGroupIngress' :: AuthorizeClusterSecurityGroupIngress -> Maybe Text
$sel:cidrip:AuthorizeClusterSecurityGroupIngress' :: AuthorizeClusterSecurityGroupIngress -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"AuthorizeClusterSecurityGroupIngress" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2012-12-01" :: Prelude.ByteString),
        ByteString
"CIDRIP" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
cidrip,
        ByteString
"EC2SecurityGroupName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
eC2SecurityGroupName,
        ByteString
"EC2SecurityGroupOwnerId"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
eC2SecurityGroupOwnerId,
        ByteString
"ClusterSecurityGroupName"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
clusterSecurityGroupName
      ]

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

-- |
-- Create a value of 'AuthorizeClusterSecurityGroupIngressResponse' 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:
--
-- 'clusterSecurityGroup', 'authorizeClusterSecurityGroupIngressResponse_clusterSecurityGroup' - Undocumented member.
--
-- 'httpStatus', 'authorizeClusterSecurityGroupIngressResponse_httpStatus' - The response's http status code.
newAuthorizeClusterSecurityGroupIngressResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  AuthorizeClusterSecurityGroupIngressResponse
newAuthorizeClusterSecurityGroupIngressResponse :: Int -> AuthorizeClusterSecurityGroupIngressResponse
newAuthorizeClusterSecurityGroupIngressResponse
  Int
pHttpStatus_ =
    AuthorizeClusterSecurityGroupIngressResponse'
      { $sel:clusterSecurityGroup:AuthorizeClusterSecurityGroupIngressResponse' :: Maybe ClusterSecurityGroup
clusterSecurityGroup =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:AuthorizeClusterSecurityGroupIngressResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | Undocumented member.
authorizeClusterSecurityGroupIngressResponse_clusterSecurityGroup :: Lens.Lens' AuthorizeClusterSecurityGroupIngressResponse (Prelude.Maybe ClusterSecurityGroup)
authorizeClusterSecurityGroupIngressResponse_clusterSecurityGroup :: Lens'
  AuthorizeClusterSecurityGroupIngressResponse
  (Maybe ClusterSecurityGroup)
authorizeClusterSecurityGroupIngressResponse_clusterSecurityGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AuthorizeClusterSecurityGroupIngressResponse' {Maybe ClusterSecurityGroup
clusterSecurityGroup :: Maybe ClusterSecurityGroup
$sel:clusterSecurityGroup:AuthorizeClusterSecurityGroupIngressResponse' :: AuthorizeClusterSecurityGroupIngressResponse
-> Maybe ClusterSecurityGroup
clusterSecurityGroup} -> Maybe ClusterSecurityGroup
clusterSecurityGroup) (\s :: AuthorizeClusterSecurityGroupIngressResponse
s@AuthorizeClusterSecurityGroupIngressResponse' {} Maybe ClusterSecurityGroup
a -> AuthorizeClusterSecurityGroupIngressResponse
s {$sel:clusterSecurityGroup:AuthorizeClusterSecurityGroupIngressResponse' :: Maybe ClusterSecurityGroup
clusterSecurityGroup = Maybe ClusterSecurityGroup
a} :: AuthorizeClusterSecurityGroupIngressResponse)

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

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