{-# 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.EC2.ModifySecurityGroupRules
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Modifies the rules of a security group.
module Amazonka.EC2.ModifySecurityGroupRules
  ( -- * Creating a Request
    ModifySecurityGroupRules (..),
    newModifySecurityGroupRules,

    -- * Request Lenses
    modifySecurityGroupRules_dryRun,
    modifySecurityGroupRules_groupId,
    modifySecurityGroupRules_securityGroupRules,

    -- * Destructuring the Response
    ModifySecurityGroupRulesResponse (..),
    newModifySecurityGroupRulesResponse,

    -- * Response Lenses
    modifySecurityGroupRulesResponse_return,
    modifySecurityGroupRulesResponse_httpStatus,
  )
where

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

-- | /See:/ 'newModifySecurityGroupRules' smart constructor.
data ModifySecurityGroupRules = ModifySecurityGroupRules'
  { -- | Checks whether you have the required permissions for the action, without
    -- actually making the request, and provides an error response. If you have
    -- the required permissions, the error response is @DryRunOperation@.
    -- Otherwise, it is @UnauthorizedOperation@.
    ModifySecurityGroupRules -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the security group.
    ModifySecurityGroupRules -> Text
groupId :: Prelude.Text,
    -- | Information about the security group properties to update.
    ModifySecurityGroupRules -> [SecurityGroupRuleUpdate]
securityGroupRules :: [SecurityGroupRuleUpdate]
  }
  deriving (ModifySecurityGroupRules -> ModifySecurityGroupRules -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModifySecurityGroupRules -> ModifySecurityGroupRules -> Bool
$c/= :: ModifySecurityGroupRules -> ModifySecurityGroupRules -> Bool
== :: ModifySecurityGroupRules -> ModifySecurityGroupRules -> Bool
$c== :: ModifySecurityGroupRules -> ModifySecurityGroupRules -> Bool
Prelude.Eq, ReadPrec [ModifySecurityGroupRules]
ReadPrec ModifySecurityGroupRules
Int -> ReadS ModifySecurityGroupRules
ReadS [ModifySecurityGroupRules]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModifySecurityGroupRules]
$creadListPrec :: ReadPrec [ModifySecurityGroupRules]
readPrec :: ReadPrec ModifySecurityGroupRules
$creadPrec :: ReadPrec ModifySecurityGroupRules
readList :: ReadS [ModifySecurityGroupRules]
$creadList :: ReadS [ModifySecurityGroupRules]
readsPrec :: Int -> ReadS ModifySecurityGroupRules
$creadsPrec :: Int -> ReadS ModifySecurityGroupRules
Prelude.Read, Int -> ModifySecurityGroupRules -> ShowS
[ModifySecurityGroupRules] -> ShowS
ModifySecurityGroupRules -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModifySecurityGroupRules] -> ShowS
$cshowList :: [ModifySecurityGroupRules] -> ShowS
show :: ModifySecurityGroupRules -> String
$cshow :: ModifySecurityGroupRules -> String
showsPrec :: Int -> ModifySecurityGroupRules -> ShowS
$cshowsPrec :: Int -> ModifySecurityGroupRules -> ShowS
Prelude.Show, forall x.
Rep ModifySecurityGroupRules x -> ModifySecurityGroupRules
forall x.
ModifySecurityGroupRules -> Rep ModifySecurityGroupRules x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ModifySecurityGroupRules x -> ModifySecurityGroupRules
$cfrom :: forall x.
ModifySecurityGroupRules -> Rep ModifySecurityGroupRules x
Prelude.Generic)

-- |
-- Create a value of 'ModifySecurityGroupRules' 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:
--
-- 'dryRun', 'modifySecurityGroupRules_dryRun' - Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
--
-- 'groupId', 'modifySecurityGroupRules_groupId' - The ID of the security group.
--
-- 'securityGroupRules', 'modifySecurityGroupRules_securityGroupRules' - Information about the security group properties to update.
newModifySecurityGroupRules ::
  -- | 'groupId'
  Prelude.Text ->
  ModifySecurityGroupRules
newModifySecurityGroupRules :: Text -> ModifySecurityGroupRules
newModifySecurityGroupRules Text
pGroupId_ =
  ModifySecurityGroupRules'
    { $sel:dryRun:ModifySecurityGroupRules' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:groupId:ModifySecurityGroupRules' :: Text
groupId = Text
pGroupId_,
      $sel:securityGroupRules:ModifySecurityGroupRules' :: [SecurityGroupRuleUpdate]
securityGroupRules = forall a. Monoid a => a
Prelude.mempty
    }

-- | Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
modifySecurityGroupRules_dryRun :: Lens.Lens' ModifySecurityGroupRules (Prelude.Maybe Prelude.Bool)
modifySecurityGroupRules_dryRun :: Lens' ModifySecurityGroupRules (Maybe Bool)
modifySecurityGroupRules_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifySecurityGroupRules' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:ModifySecurityGroupRules' :: ModifySecurityGroupRules -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: ModifySecurityGroupRules
s@ModifySecurityGroupRules' {} Maybe Bool
a -> ModifySecurityGroupRules
s {$sel:dryRun:ModifySecurityGroupRules' :: Maybe Bool
dryRun = Maybe Bool
a} :: ModifySecurityGroupRules)

-- | The ID of the security group.
modifySecurityGroupRules_groupId :: Lens.Lens' ModifySecurityGroupRules Prelude.Text
modifySecurityGroupRules_groupId :: Lens' ModifySecurityGroupRules Text
modifySecurityGroupRules_groupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifySecurityGroupRules' {Text
groupId :: Text
$sel:groupId:ModifySecurityGroupRules' :: ModifySecurityGroupRules -> Text
groupId} -> Text
groupId) (\s :: ModifySecurityGroupRules
s@ModifySecurityGroupRules' {} Text
a -> ModifySecurityGroupRules
s {$sel:groupId:ModifySecurityGroupRules' :: Text
groupId = Text
a} :: ModifySecurityGroupRules)

-- | Information about the security group properties to update.
modifySecurityGroupRules_securityGroupRules :: Lens.Lens' ModifySecurityGroupRules [SecurityGroupRuleUpdate]
modifySecurityGroupRules_securityGroupRules :: Lens' ModifySecurityGroupRules [SecurityGroupRuleUpdate]
modifySecurityGroupRules_securityGroupRules = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifySecurityGroupRules' {[SecurityGroupRuleUpdate]
securityGroupRules :: [SecurityGroupRuleUpdate]
$sel:securityGroupRules:ModifySecurityGroupRules' :: ModifySecurityGroupRules -> [SecurityGroupRuleUpdate]
securityGroupRules} -> [SecurityGroupRuleUpdate]
securityGroupRules) (\s :: ModifySecurityGroupRules
s@ModifySecurityGroupRules' {} [SecurityGroupRuleUpdate]
a -> ModifySecurityGroupRules
s {$sel:securityGroupRules:ModifySecurityGroupRules' :: [SecurityGroupRuleUpdate]
securityGroupRules = [SecurityGroupRuleUpdate]
a} :: ModifySecurityGroupRules) 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 ModifySecurityGroupRules where
  type
    AWSResponse ModifySecurityGroupRules =
      ModifySecurityGroupRulesResponse
  request :: (Service -> Service)
-> ModifySecurityGroupRules -> Request ModifySecurityGroupRules
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 ModifySecurityGroupRules
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ModifySecurityGroupRules)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Bool -> Int -> ModifySecurityGroupRulesResponse
ModifySecurityGroupRulesResponse'
            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
"return")
            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 ModifySecurityGroupRules where
  hashWithSalt :: Int -> ModifySecurityGroupRules -> Int
hashWithSalt Int
_salt ModifySecurityGroupRules' {[SecurityGroupRuleUpdate]
Maybe Bool
Text
securityGroupRules :: [SecurityGroupRuleUpdate]
groupId :: Text
dryRun :: Maybe Bool
$sel:securityGroupRules:ModifySecurityGroupRules' :: ModifySecurityGroupRules -> [SecurityGroupRuleUpdate]
$sel:groupId:ModifySecurityGroupRules' :: ModifySecurityGroupRules -> Text
$sel:dryRun:ModifySecurityGroupRules' :: ModifySecurityGroupRules -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
groupId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [SecurityGroupRuleUpdate]
securityGroupRules

instance Prelude.NFData ModifySecurityGroupRules where
  rnf :: ModifySecurityGroupRules -> ()
rnf ModifySecurityGroupRules' {[SecurityGroupRuleUpdate]
Maybe Bool
Text
securityGroupRules :: [SecurityGroupRuleUpdate]
groupId :: Text
dryRun :: Maybe Bool
$sel:securityGroupRules:ModifySecurityGroupRules' :: ModifySecurityGroupRules -> [SecurityGroupRuleUpdate]
$sel:groupId:ModifySecurityGroupRules' :: ModifySecurityGroupRules -> Text
$sel:dryRun:ModifySecurityGroupRules' :: ModifySecurityGroupRules -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dryRun
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
groupId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [SecurityGroupRuleUpdate]
securityGroupRules

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

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

instance Data.ToQuery ModifySecurityGroupRules where
  toQuery :: ModifySecurityGroupRules -> QueryString
toQuery ModifySecurityGroupRules' {[SecurityGroupRuleUpdate]
Maybe Bool
Text
securityGroupRules :: [SecurityGroupRuleUpdate]
groupId :: Text
dryRun :: Maybe Bool
$sel:securityGroupRules:ModifySecurityGroupRules' :: ModifySecurityGroupRules -> [SecurityGroupRuleUpdate]
$sel:groupId:ModifySecurityGroupRules' :: ModifySecurityGroupRules -> Text
$sel:dryRun:ModifySecurityGroupRules' :: ModifySecurityGroupRules -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"ModifySecurityGroupRules" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        ByteString
"GroupId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
groupId,
        forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList
          ByteString
"SecurityGroupRule"
          [SecurityGroupRuleUpdate]
securityGroupRules
      ]

-- | /See:/ 'newModifySecurityGroupRulesResponse' smart constructor.
data ModifySecurityGroupRulesResponse = ModifySecurityGroupRulesResponse'
  { -- | Returns @true@ if the request succeeds; otherwise, returns an error.
    ModifySecurityGroupRulesResponse -> Maybe Bool
return' :: Prelude.Maybe Prelude.Bool,
    -- | The response's http status code.
    ModifySecurityGroupRulesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ModifySecurityGroupRulesResponse
-> ModifySecurityGroupRulesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModifySecurityGroupRulesResponse
-> ModifySecurityGroupRulesResponse -> Bool
$c/= :: ModifySecurityGroupRulesResponse
-> ModifySecurityGroupRulesResponse -> Bool
== :: ModifySecurityGroupRulesResponse
-> ModifySecurityGroupRulesResponse -> Bool
$c== :: ModifySecurityGroupRulesResponse
-> ModifySecurityGroupRulesResponse -> Bool
Prelude.Eq, ReadPrec [ModifySecurityGroupRulesResponse]
ReadPrec ModifySecurityGroupRulesResponse
Int -> ReadS ModifySecurityGroupRulesResponse
ReadS [ModifySecurityGroupRulesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModifySecurityGroupRulesResponse]
$creadListPrec :: ReadPrec [ModifySecurityGroupRulesResponse]
readPrec :: ReadPrec ModifySecurityGroupRulesResponse
$creadPrec :: ReadPrec ModifySecurityGroupRulesResponse
readList :: ReadS [ModifySecurityGroupRulesResponse]
$creadList :: ReadS [ModifySecurityGroupRulesResponse]
readsPrec :: Int -> ReadS ModifySecurityGroupRulesResponse
$creadsPrec :: Int -> ReadS ModifySecurityGroupRulesResponse
Prelude.Read, Int -> ModifySecurityGroupRulesResponse -> ShowS
[ModifySecurityGroupRulesResponse] -> ShowS
ModifySecurityGroupRulesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModifySecurityGroupRulesResponse] -> ShowS
$cshowList :: [ModifySecurityGroupRulesResponse] -> ShowS
show :: ModifySecurityGroupRulesResponse -> String
$cshow :: ModifySecurityGroupRulesResponse -> String
showsPrec :: Int -> ModifySecurityGroupRulesResponse -> ShowS
$cshowsPrec :: Int -> ModifySecurityGroupRulesResponse -> ShowS
Prelude.Show, forall x.
Rep ModifySecurityGroupRulesResponse x
-> ModifySecurityGroupRulesResponse
forall x.
ModifySecurityGroupRulesResponse
-> Rep ModifySecurityGroupRulesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ModifySecurityGroupRulesResponse x
-> ModifySecurityGroupRulesResponse
$cfrom :: forall x.
ModifySecurityGroupRulesResponse
-> Rep ModifySecurityGroupRulesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ModifySecurityGroupRulesResponse' 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:
--
-- 'return'', 'modifySecurityGroupRulesResponse_return' - Returns @true@ if the request succeeds; otherwise, returns an error.
--
-- 'httpStatus', 'modifySecurityGroupRulesResponse_httpStatus' - The response's http status code.
newModifySecurityGroupRulesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ModifySecurityGroupRulesResponse
newModifySecurityGroupRulesResponse :: Int -> ModifySecurityGroupRulesResponse
newModifySecurityGroupRulesResponse Int
pHttpStatus_ =
  ModifySecurityGroupRulesResponse'
    { $sel:return':ModifySecurityGroupRulesResponse' :: Maybe Bool
return' =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ModifySecurityGroupRulesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Returns @true@ if the request succeeds; otherwise, returns an error.
modifySecurityGroupRulesResponse_return :: Lens.Lens' ModifySecurityGroupRulesResponse (Prelude.Maybe Prelude.Bool)
modifySecurityGroupRulesResponse_return :: Lens' ModifySecurityGroupRulesResponse (Maybe Bool)
modifySecurityGroupRulesResponse_return = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifySecurityGroupRulesResponse' {Maybe Bool
return' :: Maybe Bool
$sel:return':ModifySecurityGroupRulesResponse' :: ModifySecurityGroupRulesResponse -> Maybe Bool
return'} -> Maybe Bool
return') (\s :: ModifySecurityGroupRulesResponse
s@ModifySecurityGroupRulesResponse' {} Maybe Bool
a -> ModifySecurityGroupRulesResponse
s {$sel:return':ModifySecurityGroupRulesResponse' :: Maybe Bool
return' = Maybe Bool
a} :: ModifySecurityGroupRulesResponse)

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

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