{-# 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.ELBV2.SetSecurityGroups
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Associates the specified security groups with the specified Application
-- Load Balancer. The specified security groups override the previously
-- associated security groups.
--
-- You can\'t specify a security group for a Network Load Balancer or
-- Gateway Load Balancer.
module Amazonka.ELBV2.SetSecurityGroups
  ( -- * Creating a Request
    SetSecurityGroups (..),
    newSetSecurityGroups,

    -- * Request Lenses
    setSecurityGroups_loadBalancerArn,
    setSecurityGroups_securityGroups,

    -- * Destructuring the Response
    SetSecurityGroupsResponse (..),
    newSetSecurityGroupsResponse,

    -- * Response Lenses
    setSecurityGroupsResponse_securityGroupIds,
    setSecurityGroupsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newSetSecurityGroups' smart constructor.
data SetSecurityGroups = SetSecurityGroups'
  { -- | The Amazon Resource Name (ARN) of the load balancer.
    SetSecurityGroups -> Text
loadBalancerArn :: Prelude.Text,
    -- | The IDs of the security groups.
    SetSecurityGroups -> [Text]
securityGroups :: [Prelude.Text]
  }
  deriving (SetSecurityGroups -> SetSecurityGroups -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetSecurityGroups -> SetSecurityGroups -> Bool
$c/= :: SetSecurityGroups -> SetSecurityGroups -> Bool
== :: SetSecurityGroups -> SetSecurityGroups -> Bool
$c== :: SetSecurityGroups -> SetSecurityGroups -> Bool
Prelude.Eq, ReadPrec [SetSecurityGroups]
ReadPrec SetSecurityGroups
Int -> ReadS SetSecurityGroups
ReadS [SetSecurityGroups]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SetSecurityGroups]
$creadListPrec :: ReadPrec [SetSecurityGroups]
readPrec :: ReadPrec SetSecurityGroups
$creadPrec :: ReadPrec SetSecurityGroups
readList :: ReadS [SetSecurityGroups]
$creadList :: ReadS [SetSecurityGroups]
readsPrec :: Int -> ReadS SetSecurityGroups
$creadsPrec :: Int -> ReadS SetSecurityGroups
Prelude.Read, Int -> SetSecurityGroups -> ShowS
[SetSecurityGroups] -> ShowS
SetSecurityGroups -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetSecurityGroups] -> ShowS
$cshowList :: [SetSecurityGroups] -> ShowS
show :: SetSecurityGroups -> String
$cshow :: SetSecurityGroups -> String
showsPrec :: Int -> SetSecurityGroups -> ShowS
$cshowsPrec :: Int -> SetSecurityGroups -> ShowS
Prelude.Show, forall x. Rep SetSecurityGroups x -> SetSecurityGroups
forall x. SetSecurityGroups -> Rep SetSecurityGroups x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetSecurityGroups x -> SetSecurityGroups
$cfrom :: forall x. SetSecurityGroups -> Rep SetSecurityGroups x
Prelude.Generic)

-- |
-- Create a value of 'SetSecurityGroups' 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:
--
-- 'loadBalancerArn', 'setSecurityGroups_loadBalancerArn' - The Amazon Resource Name (ARN) of the load balancer.
--
-- 'securityGroups', 'setSecurityGroups_securityGroups' - The IDs of the security groups.
newSetSecurityGroups ::
  -- | 'loadBalancerArn'
  Prelude.Text ->
  SetSecurityGroups
newSetSecurityGroups :: Text -> SetSecurityGroups
newSetSecurityGroups Text
pLoadBalancerArn_ =
  SetSecurityGroups'
    { $sel:loadBalancerArn:SetSecurityGroups' :: Text
loadBalancerArn =
        Text
pLoadBalancerArn_,
      $sel:securityGroups:SetSecurityGroups' :: [Text]
securityGroups = forall a. Monoid a => a
Prelude.mempty
    }

-- | The Amazon Resource Name (ARN) of the load balancer.
setSecurityGroups_loadBalancerArn :: Lens.Lens' SetSecurityGroups Prelude.Text
setSecurityGroups_loadBalancerArn :: Lens' SetSecurityGroups Text
setSecurityGroups_loadBalancerArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SetSecurityGroups' {Text
loadBalancerArn :: Text
$sel:loadBalancerArn:SetSecurityGroups' :: SetSecurityGroups -> Text
loadBalancerArn} -> Text
loadBalancerArn) (\s :: SetSecurityGroups
s@SetSecurityGroups' {} Text
a -> SetSecurityGroups
s {$sel:loadBalancerArn:SetSecurityGroups' :: Text
loadBalancerArn = Text
a} :: SetSecurityGroups)

-- | The IDs of the security groups.
setSecurityGroups_securityGroups :: Lens.Lens' SetSecurityGroups [Prelude.Text]
setSecurityGroups_securityGroups :: Lens' SetSecurityGroups [Text]
setSecurityGroups_securityGroups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SetSecurityGroups' {[Text]
securityGroups :: [Text]
$sel:securityGroups:SetSecurityGroups' :: SetSecurityGroups -> [Text]
securityGroups} -> [Text]
securityGroups) (\s :: SetSecurityGroups
s@SetSecurityGroups' {} [Text]
a -> SetSecurityGroups
s {$sel:securityGroups:SetSecurityGroups' :: [Text]
securityGroups = [Text]
a} :: SetSecurityGroups) 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

instance Core.AWSRequest SetSecurityGroups where
  type
    AWSResponse SetSecurityGroups =
      SetSecurityGroupsResponse
  request :: (Service -> Service)
-> SetSecurityGroups -> Request SetSecurityGroups
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 SetSecurityGroups
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse SetSecurityGroups)))
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
"SetSecurityGroupsResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe [Text] -> Int -> SetSecurityGroupsResponse
SetSecurityGroupsResponse'
            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
"SecurityGroupIds"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                        )
            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 SetSecurityGroups where
  hashWithSalt :: Int -> SetSecurityGroups -> Int
hashWithSalt Int
_salt SetSecurityGroups' {[Text]
Text
securityGroups :: [Text]
loadBalancerArn :: Text
$sel:securityGroups:SetSecurityGroups' :: SetSecurityGroups -> [Text]
$sel:loadBalancerArn:SetSecurityGroups' :: SetSecurityGroups -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
loadBalancerArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
securityGroups

instance Prelude.NFData SetSecurityGroups where
  rnf :: SetSecurityGroups -> ()
rnf SetSecurityGroups' {[Text]
Text
securityGroups :: [Text]
loadBalancerArn :: Text
$sel:securityGroups:SetSecurityGroups' :: SetSecurityGroups -> [Text]
$sel:loadBalancerArn:SetSecurityGroups' :: SetSecurityGroups -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
loadBalancerArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
securityGroups

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

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

instance Data.ToQuery SetSecurityGroups where
  toQuery :: SetSecurityGroups -> QueryString
toQuery SetSecurityGroups' {[Text]
Text
securityGroups :: [Text]
loadBalancerArn :: Text
$sel:securityGroups:SetSecurityGroups' :: SetSecurityGroups -> [Text]
$sel:loadBalancerArn:SetSecurityGroups' :: SetSecurityGroups -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"SetSecurityGroups" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2015-12-01" :: Prelude.ByteString),
        ByteString
"LoadBalancerArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
loadBalancerArn,
        ByteString
"SecurityGroups"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" [Text]
securityGroups
      ]

-- | /See:/ 'newSetSecurityGroupsResponse' smart constructor.
data SetSecurityGroupsResponse = SetSecurityGroupsResponse'
  { -- | The IDs of the security groups associated with the load balancer.
    SetSecurityGroupsResponse -> Maybe [Text]
securityGroupIds :: Prelude.Maybe [Prelude.Text],
    -- | The response's http status code.
    SetSecurityGroupsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (SetSecurityGroupsResponse -> SetSecurityGroupsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetSecurityGroupsResponse -> SetSecurityGroupsResponse -> Bool
$c/= :: SetSecurityGroupsResponse -> SetSecurityGroupsResponse -> Bool
== :: SetSecurityGroupsResponse -> SetSecurityGroupsResponse -> Bool
$c== :: SetSecurityGroupsResponse -> SetSecurityGroupsResponse -> Bool
Prelude.Eq, ReadPrec [SetSecurityGroupsResponse]
ReadPrec SetSecurityGroupsResponse
Int -> ReadS SetSecurityGroupsResponse
ReadS [SetSecurityGroupsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SetSecurityGroupsResponse]
$creadListPrec :: ReadPrec [SetSecurityGroupsResponse]
readPrec :: ReadPrec SetSecurityGroupsResponse
$creadPrec :: ReadPrec SetSecurityGroupsResponse
readList :: ReadS [SetSecurityGroupsResponse]
$creadList :: ReadS [SetSecurityGroupsResponse]
readsPrec :: Int -> ReadS SetSecurityGroupsResponse
$creadsPrec :: Int -> ReadS SetSecurityGroupsResponse
Prelude.Read, Int -> SetSecurityGroupsResponse -> ShowS
[SetSecurityGroupsResponse] -> ShowS
SetSecurityGroupsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetSecurityGroupsResponse] -> ShowS
$cshowList :: [SetSecurityGroupsResponse] -> ShowS
show :: SetSecurityGroupsResponse -> String
$cshow :: SetSecurityGroupsResponse -> String
showsPrec :: Int -> SetSecurityGroupsResponse -> ShowS
$cshowsPrec :: Int -> SetSecurityGroupsResponse -> ShowS
Prelude.Show, forall x.
Rep SetSecurityGroupsResponse x -> SetSecurityGroupsResponse
forall x.
SetSecurityGroupsResponse -> Rep SetSecurityGroupsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SetSecurityGroupsResponse x -> SetSecurityGroupsResponse
$cfrom :: forall x.
SetSecurityGroupsResponse -> Rep SetSecurityGroupsResponse x
Prelude.Generic)

-- |
-- Create a value of 'SetSecurityGroupsResponse' 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:
--
-- 'securityGroupIds', 'setSecurityGroupsResponse_securityGroupIds' - The IDs of the security groups associated with the load balancer.
--
-- 'httpStatus', 'setSecurityGroupsResponse_httpStatus' - The response's http status code.
newSetSecurityGroupsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  SetSecurityGroupsResponse
newSetSecurityGroupsResponse :: Int -> SetSecurityGroupsResponse
newSetSecurityGroupsResponse Int
pHttpStatus_ =
  SetSecurityGroupsResponse'
    { $sel:securityGroupIds:SetSecurityGroupsResponse' :: Maybe [Text]
securityGroupIds =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:SetSecurityGroupsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The IDs of the security groups associated with the load balancer.
setSecurityGroupsResponse_securityGroupIds :: Lens.Lens' SetSecurityGroupsResponse (Prelude.Maybe [Prelude.Text])
setSecurityGroupsResponse_securityGroupIds :: Lens' SetSecurityGroupsResponse (Maybe [Text])
setSecurityGroupsResponse_securityGroupIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SetSecurityGroupsResponse' {Maybe [Text]
securityGroupIds :: Maybe [Text]
$sel:securityGroupIds:SetSecurityGroupsResponse' :: SetSecurityGroupsResponse -> Maybe [Text]
securityGroupIds} -> Maybe [Text]
securityGroupIds) (\s :: SetSecurityGroupsResponse
s@SetSecurityGroupsResponse' {} Maybe [Text]
a -> SetSecurityGroupsResponse
s {$sel:securityGroupIds:SetSecurityGroupsResponse' :: Maybe [Text]
securityGroupIds = Maybe [Text]
a} :: SetSecurityGroupsResponse) 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 response's http status code.
setSecurityGroupsResponse_httpStatus :: Lens.Lens' SetSecurityGroupsResponse Prelude.Int
setSecurityGroupsResponse_httpStatus :: Lens' SetSecurityGroupsResponse Int
setSecurityGroupsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SetSecurityGroupsResponse' {Int
httpStatus :: Int
$sel:httpStatus:SetSecurityGroupsResponse' :: SetSecurityGroupsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: SetSecurityGroupsResponse
s@SetSecurityGroupsResponse' {} Int
a -> SetSecurityGroupsResponse
s {$sel:httpStatus:SetSecurityGroupsResponse' :: Int
httpStatus = Int
a} :: SetSecurityGroupsResponse)

instance Prelude.NFData SetSecurityGroupsResponse where
  rnf :: SetSecurityGroupsResponse -> ()
rnf SetSecurityGroupsResponse' {Int
Maybe [Text]
httpStatus :: Int
securityGroupIds :: Maybe [Text]
$sel:httpStatus:SetSecurityGroupsResponse' :: SetSecurityGroupsResponse -> Int
$sel:securityGroupIds:SetSecurityGroupsResponse' :: SetSecurityGroupsResponse -> Maybe [Text]
..} =
    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 Int
httpStatus