{-# 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.CreateSecurityGroup
-- 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 security group.
--
-- A security group acts as a virtual firewall for your instance to control
-- inbound and outbound traffic. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/using-network-security.html Amazon EC2 security groups>
-- in the /Amazon Elastic Compute Cloud User Guide/ and
-- <https://docs.aws.amazon.com/AmazonVPC/latest/UserGuide/VPC_SecurityGroups.html Security groups for your VPC>
-- in the /Amazon Virtual Private Cloud User Guide/.
--
-- When you create a security group, you specify a friendly name of your
-- choice. You can have a security group for use in EC2-Classic with the
-- same name as a security group for use in a VPC. However, you can\'t have
-- two security groups for use in EC2-Classic with the same name or two
-- security groups for use in a VPC with the same name.
--
-- You have a default security group for use in EC2-Classic and a default
-- security group for use in your VPC. If you don\'t specify a security
-- group when you launch an instance, the instance is launched into the
-- appropriate default security group. A default security group includes a
-- default rule that grants instances unrestricted network access to each
-- other.
--
-- You can add or remove rules from your security groups using
-- AuthorizeSecurityGroupIngress, AuthorizeSecurityGroupEgress,
-- RevokeSecurityGroupIngress, and RevokeSecurityGroupEgress.
--
-- For more information about VPC security group limits, see
-- <https://docs.aws.amazon.com/vpc/latest/userguide/amazon-vpc-limits.html Amazon VPC Limits>.
--
-- We are retiring EC2-Classic. We recommend that you migrate from
-- EC2-Classic to a VPC. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/vpc-migrate.html Migrate from EC2-Classic to a VPC>
-- in the /Amazon Elastic Compute Cloud User Guide/.
module Amazonka.EC2.CreateSecurityGroup
  ( -- * Creating a Request
    CreateSecurityGroup (..),
    newCreateSecurityGroup,

    -- * Request Lenses
    createSecurityGroup_dryRun,
    createSecurityGroup_tagSpecifications,
    createSecurityGroup_vpcId,
    createSecurityGroup_description,
    createSecurityGroup_groupName,

    -- * Destructuring the Response
    CreateSecurityGroupResponse (..),
    newCreateSecurityGroupResponse,

    -- * Response Lenses
    createSecurityGroupResponse_tags,
    createSecurityGroupResponse_httpStatus,
    createSecurityGroupResponse_groupId,
  )
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:/ 'newCreateSecurityGroup' smart constructor.
data CreateSecurityGroup = CreateSecurityGroup'
  { -- | 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@.
    CreateSecurityGroup -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The tags to assign to the security group.
    CreateSecurityGroup -> Maybe [TagSpecification]
tagSpecifications :: Prelude.Maybe [TagSpecification],
    -- | [EC2-VPC] The ID of the VPC. Required for EC2-VPC.
    CreateSecurityGroup -> Maybe Text
vpcId :: Prelude.Maybe Prelude.Text,
    -- | A description for the security group. This is informational only.
    --
    -- Constraints: Up to 255 characters in length
    --
    -- Constraints for EC2-Classic: ASCII characters
    --
    -- Constraints for EC2-VPC: a-z, A-Z, 0-9, spaces, and
    -- ._-:\/()#,\@[]+=&;{}!$*
    CreateSecurityGroup -> Text
description :: Prelude.Text,
    -- | The name of the security group.
    --
    -- Constraints: Up to 255 characters in length. Cannot start with @sg-@.
    --
    -- Constraints for EC2-Classic: ASCII characters
    --
    -- Constraints for EC2-VPC: a-z, A-Z, 0-9, spaces, and
    -- ._-:\/()#,\@[]+=&;{}!$*
    CreateSecurityGroup -> Text
groupName :: Prelude.Text
  }
  deriving (CreateSecurityGroup -> CreateSecurityGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateSecurityGroup -> CreateSecurityGroup -> Bool
$c/= :: CreateSecurityGroup -> CreateSecurityGroup -> Bool
== :: CreateSecurityGroup -> CreateSecurityGroup -> Bool
$c== :: CreateSecurityGroup -> CreateSecurityGroup -> Bool
Prelude.Eq, ReadPrec [CreateSecurityGroup]
ReadPrec CreateSecurityGroup
Int -> ReadS CreateSecurityGroup
ReadS [CreateSecurityGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateSecurityGroup]
$creadListPrec :: ReadPrec [CreateSecurityGroup]
readPrec :: ReadPrec CreateSecurityGroup
$creadPrec :: ReadPrec CreateSecurityGroup
readList :: ReadS [CreateSecurityGroup]
$creadList :: ReadS [CreateSecurityGroup]
readsPrec :: Int -> ReadS CreateSecurityGroup
$creadsPrec :: Int -> ReadS CreateSecurityGroup
Prelude.Read, Int -> CreateSecurityGroup -> ShowS
[CreateSecurityGroup] -> ShowS
CreateSecurityGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateSecurityGroup] -> ShowS
$cshowList :: [CreateSecurityGroup] -> ShowS
show :: CreateSecurityGroup -> String
$cshow :: CreateSecurityGroup -> String
showsPrec :: Int -> CreateSecurityGroup -> ShowS
$cshowsPrec :: Int -> CreateSecurityGroup -> ShowS
Prelude.Show, forall x. Rep CreateSecurityGroup x -> CreateSecurityGroup
forall x. CreateSecurityGroup -> Rep CreateSecurityGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateSecurityGroup x -> CreateSecurityGroup
$cfrom :: forall x. CreateSecurityGroup -> Rep CreateSecurityGroup x
Prelude.Generic)

-- |
-- Create a value of 'CreateSecurityGroup' 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', 'createSecurityGroup_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@.
--
-- 'tagSpecifications', 'createSecurityGroup_tagSpecifications' - The tags to assign to the security group.
--
-- 'vpcId', 'createSecurityGroup_vpcId' - [EC2-VPC] The ID of the VPC. Required for EC2-VPC.
--
-- 'description', 'createSecurityGroup_description' - A description for the security group. This is informational only.
--
-- Constraints: Up to 255 characters in length
--
-- Constraints for EC2-Classic: ASCII characters
--
-- Constraints for EC2-VPC: a-z, A-Z, 0-9, spaces, and
-- ._-:\/()#,\@[]+=&;{}!$*
--
-- 'groupName', 'createSecurityGroup_groupName' - The name of the security group.
--
-- Constraints: Up to 255 characters in length. Cannot start with @sg-@.
--
-- Constraints for EC2-Classic: ASCII characters
--
-- Constraints for EC2-VPC: a-z, A-Z, 0-9, spaces, and
-- ._-:\/()#,\@[]+=&;{}!$*
newCreateSecurityGroup ::
  -- | 'description'
  Prelude.Text ->
  -- | 'groupName'
  Prelude.Text ->
  CreateSecurityGroup
newCreateSecurityGroup :: Text -> Text -> CreateSecurityGroup
newCreateSecurityGroup Text
pDescription_ Text
pGroupName_ =
  CreateSecurityGroup'
    { $sel:dryRun:CreateSecurityGroup' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:tagSpecifications:CreateSecurityGroup' :: Maybe [TagSpecification]
tagSpecifications = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcId:CreateSecurityGroup' :: Maybe Text
vpcId = forall a. Maybe a
Prelude.Nothing,
      $sel:description:CreateSecurityGroup' :: Text
description = Text
pDescription_,
      $sel:groupName:CreateSecurityGroup' :: Text
groupName = Text
pGroupName_
    }

-- | 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@.
createSecurityGroup_dryRun :: Lens.Lens' CreateSecurityGroup (Prelude.Maybe Prelude.Bool)
createSecurityGroup_dryRun :: Lens' CreateSecurityGroup (Maybe Bool)
createSecurityGroup_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSecurityGroup' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:CreateSecurityGroup' :: CreateSecurityGroup -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: CreateSecurityGroup
s@CreateSecurityGroup' {} Maybe Bool
a -> CreateSecurityGroup
s {$sel:dryRun:CreateSecurityGroup' :: Maybe Bool
dryRun = Maybe Bool
a} :: CreateSecurityGroup)

-- | The tags to assign to the security group.
createSecurityGroup_tagSpecifications :: Lens.Lens' CreateSecurityGroup (Prelude.Maybe [TagSpecification])
createSecurityGroup_tagSpecifications :: Lens' CreateSecurityGroup (Maybe [TagSpecification])
createSecurityGroup_tagSpecifications = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSecurityGroup' {Maybe [TagSpecification]
tagSpecifications :: Maybe [TagSpecification]
$sel:tagSpecifications:CreateSecurityGroup' :: CreateSecurityGroup -> Maybe [TagSpecification]
tagSpecifications} -> Maybe [TagSpecification]
tagSpecifications) (\s :: CreateSecurityGroup
s@CreateSecurityGroup' {} Maybe [TagSpecification]
a -> CreateSecurityGroup
s {$sel:tagSpecifications:CreateSecurityGroup' :: Maybe [TagSpecification]
tagSpecifications = Maybe [TagSpecification]
a} :: CreateSecurityGroup) 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

-- | [EC2-VPC] The ID of the VPC. Required for EC2-VPC.
createSecurityGroup_vpcId :: Lens.Lens' CreateSecurityGroup (Prelude.Maybe Prelude.Text)
createSecurityGroup_vpcId :: Lens' CreateSecurityGroup (Maybe Text)
createSecurityGroup_vpcId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSecurityGroup' {Maybe Text
vpcId :: Maybe Text
$sel:vpcId:CreateSecurityGroup' :: CreateSecurityGroup -> Maybe Text
vpcId} -> Maybe Text
vpcId) (\s :: CreateSecurityGroup
s@CreateSecurityGroup' {} Maybe Text
a -> CreateSecurityGroup
s {$sel:vpcId:CreateSecurityGroup' :: Maybe Text
vpcId = Maybe Text
a} :: CreateSecurityGroup)

-- | A description for the security group. This is informational only.
--
-- Constraints: Up to 255 characters in length
--
-- Constraints for EC2-Classic: ASCII characters
--
-- Constraints for EC2-VPC: a-z, A-Z, 0-9, spaces, and
-- ._-:\/()#,\@[]+=&;{}!$*
createSecurityGroup_description :: Lens.Lens' CreateSecurityGroup Prelude.Text
createSecurityGroup_description :: Lens' CreateSecurityGroup Text
createSecurityGroup_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSecurityGroup' {Text
description :: Text
$sel:description:CreateSecurityGroup' :: CreateSecurityGroup -> Text
description} -> Text
description) (\s :: CreateSecurityGroup
s@CreateSecurityGroup' {} Text
a -> CreateSecurityGroup
s {$sel:description:CreateSecurityGroup' :: Text
description = Text
a} :: CreateSecurityGroup)

-- | The name of the security group.
--
-- Constraints: Up to 255 characters in length. Cannot start with @sg-@.
--
-- Constraints for EC2-Classic: ASCII characters
--
-- Constraints for EC2-VPC: a-z, A-Z, 0-9, spaces, and
-- ._-:\/()#,\@[]+=&;{}!$*
createSecurityGroup_groupName :: Lens.Lens' CreateSecurityGroup Prelude.Text
createSecurityGroup_groupName :: Lens' CreateSecurityGroup Text
createSecurityGroup_groupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSecurityGroup' {Text
groupName :: Text
$sel:groupName:CreateSecurityGroup' :: CreateSecurityGroup -> Text
groupName} -> Text
groupName) (\s :: CreateSecurityGroup
s@CreateSecurityGroup' {} Text
a -> CreateSecurityGroup
s {$sel:groupName:CreateSecurityGroup' :: Text
groupName = Text
a} :: CreateSecurityGroup)

instance Core.AWSRequest CreateSecurityGroup where
  type
    AWSResponse CreateSecurityGroup =
      CreateSecurityGroupResponse
  request :: (Service -> Service)
-> CreateSecurityGroup -> Request CreateSecurityGroup
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 CreateSecurityGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateSecurityGroup)))
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 [Tag] -> Int -> Text -> CreateSecurityGroupResponse
CreateSecurityGroupResponse'
            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
"tagSet"
                            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
"item")
                        )
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"groupId")
      )

instance Prelude.Hashable CreateSecurityGroup where
  hashWithSalt :: Int -> CreateSecurityGroup -> Int
hashWithSalt Int
_salt CreateSecurityGroup' {Maybe Bool
Maybe [TagSpecification]
Maybe Text
Text
groupName :: Text
description :: Text
vpcId :: Maybe Text
tagSpecifications :: Maybe [TagSpecification]
dryRun :: Maybe Bool
$sel:groupName:CreateSecurityGroup' :: CreateSecurityGroup -> Text
$sel:description:CreateSecurityGroup' :: CreateSecurityGroup -> Text
$sel:vpcId:CreateSecurityGroup' :: CreateSecurityGroup -> Maybe Text
$sel:tagSpecifications:CreateSecurityGroup' :: CreateSecurityGroup -> Maybe [TagSpecification]
$sel:dryRun:CreateSecurityGroup' :: CreateSecurityGroup -> 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` Maybe [TagSpecification]
tagSpecifications
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
vpcId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
groupName

instance Prelude.NFData CreateSecurityGroup where
  rnf :: CreateSecurityGroup -> ()
rnf CreateSecurityGroup' {Maybe Bool
Maybe [TagSpecification]
Maybe Text
Text
groupName :: Text
description :: Text
vpcId :: Maybe Text
tagSpecifications :: Maybe [TagSpecification]
dryRun :: Maybe Bool
$sel:groupName:CreateSecurityGroup' :: CreateSecurityGroup -> Text
$sel:description:CreateSecurityGroup' :: CreateSecurityGroup -> Text
$sel:vpcId:CreateSecurityGroup' :: CreateSecurityGroup -> Maybe Text
$sel:tagSpecifications:CreateSecurityGroup' :: CreateSecurityGroup -> Maybe [TagSpecification]
$sel:dryRun:CreateSecurityGroup' :: CreateSecurityGroup -> 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 Maybe [TagSpecification]
tagSpecifications
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
vpcId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
groupName

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

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

instance Data.ToQuery CreateSecurityGroup where
  toQuery :: CreateSecurityGroup -> QueryString
toQuery CreateSecurityGroup' {Maybe Bool
Maybe [TagSpecification]
Maybe Text
Text
groupName :: Text
description :: Text
vpcId :: Maybe Text
tagSpecifications :: Maybe [TagSpecification]
dryRun :: Maybe Bool
$sel:groupName:CreateSecurityGroup' :: CreateSecurityGroup -> Text
$sel:description:CreateSecurityGroup' :: CreateSecurityGroup -> Text
$sel:vpcId:CreateSecurityGroup' :: CreateSecurityGroup -> Maybe Text
$sel:tagSpecifications:CreateSecurityGroup' :: CreateSecurityGroup -> Maybe [TagSpecification]
$sel:dryRun:CreateSecurityGroup' :: CreateSecurityGroup -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"CreateSecurityGroup" :: 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,
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"TagSpecification"
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [TagSpecification]
tagSpecifications
          ),
        ByteString
"VpcId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
vpcId,
        ByteString
"GroupDescription" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
description,
        ByteString
"GroupName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
groupName
      ]

-- | /See:/ 'newCreateSecurityGroupResponse' smart constructor.
data CreateSecurityGroupResponse = CreateSecurityGroupResponse'
  { -- | The tags assigned to the security group.
    CreateSecurityGroupResponse -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The response's http status code.
    CreateSecurityGroupResponse -> Int
httpStatus :: Prelude.Int,
    -- | The ID of the security group.
    CreateSecurityGroupResponse -> Text
groupId :: Prelude.Text
  }
  deriving (CreateSecurityGroupResponse -> CreateSecurityGroupResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateSecurityGroupResponse -> CreateSecurityGroupResponse -> Bool
$c/= :: CreateSecurityGroupResponse -> CreateSecurityGroupResponse -> Bool
== :: CreateSecurityGroupResponse -> CreateSecurityGroupResponse -> Bool
$c== :: CreateSecurityGroupResponse -> CreateSecurityGroupResponse -> Bool
Prelude.Eq, ReadPrec [CreateSecurityGroupResponse]
ReadPrec CreateSecurityGroupResponse
Int -> ReadS CreateSecurityGroupResponse
ReadS [CreateSecurityGroupResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateSecurityGroupResponse]
$creadListPrec :: ReadPrec [CreateSecurityGroupResponse]
readPrec :: ReadPrec CreateSecurityGroupResponse
$creadPrec :: ReadPrec CreateSecurityGroupResponse
readList :: ReadS [CreateSecurityGroupResponse]
$creadList :: ReadS [CreateSecurityGroupResponse]
readsPrec :: Int -> ReadS CreateSecurityGroupResponse
$creadsPrec :: Int -> ReadS CreateSecurityGroupResponse
Prelude.Read, Int -> CreateSecurityGroupResponse -> ShowS
[CreateSecurityGroupResponse] -> ShowS
CreateSecurityGroupResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateSecurityGroupResponse] -> ShowS
$cshowList :: [CreateSecurityGroupResponse] -> ShowS
show :: CreateSecurityGroupResponse -> String
$cshow :: CreateSecurityGroupResponse -> String
showsPrec :: Int -> CreateSecurityGroupResponse -> ShowS
$cshowsPrec :: Int -> CreateSecurityGroupResponse -> ShowS
Prelude.Show, forall x.
Rep CreateSecurityGroupResponse x -> CreateSecurityGroupResponse
forall x.
CreateSecurityGroupResponse -> Rep CreateSecurityGroupResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateSecurityGroupResponse x -> CreateSecurityGroupResponse
$cfrom :: forall x.
CreateSecurityGroupResponse -> Rep CreateSecurityGroupResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateSecurityGroupResponse' 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:
--
-- 'tags', 'createSecurityGroupResponse_tags' - The tags assigned to the security group.
--
-- 'httpStatus', 'createSecurityGroupResponse_httpStatus' - The response's http status code.
--
-- 'groupId', 'createSecurityGroupResponse_groupId' - The ID of the security group.
newCreateSecurityGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'groupId'
  Prelude.Text ->
  CreateSecurityGroupResponse
newCreateSecurityGroupResponse :: Int -> Text -> CreateSecurityGroupResponse
newCreateSecurityGroupResponse Int
pHttpStatus_ Text
pGroupId_ =
  CreateSecurityGroupResponse'
    { $sel:tags:CreateSecurityGroupResponse' :: Maybe [Tag]
tags =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateSecurityGroupResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:groupId:CreateSecurityGroupResponse' :: Text
groupId = Text
pGroupId_
    }

-- | The tags assigned to the security group.
createSecurityGroupResponse_tags :: Lens.Lens' CreateSecurityGroupResponse (Prelude.Maybe [Tag])
createSecurityGroupResponse_tags :: Lens' CreateSecurityGroupResponse (Maybe [Tag])
createSecurityGroupResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSecurityGroupResponse' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateSecurityGroupResponse' :: CreateSecurityGroupResponse -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateSecurityGroupResponse
s@CreateSecurityGroupResponse' {} Maybe [Tag]
a -> CreateSecurityGroupResponse
s {$sel:tags:CreateSecurityGroupResponse' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateSecurityGroupResponse) 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.
createSecurityGroupResponse_httpStatus :: Lens.Lens' CreateSecurityGroupResponse Prelude.Int
createSecurityGroupResponse_httpStatus :: Lens' CreateSecurityGroupResponse Int
createSecurityGroupResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSecurityGroupResponse' {Int
httpStatus :: Int
$sel:httpStatus:CreateSecurityGroupResponse' :: CreateSecurityGroupResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: CreateSecurityGroupResponse
s@CreateSecurityGroupResponse' {} Int
a -> CreateSecurityGroupResponse
s {$sel:httpStatus:CreateSecurityGroupResponse' :: Int
httpStatus = Int
a} :: CreateSecurityGroupResponse)

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

instance Prelude.NFData CreateSecurityGroupResponse where
  rnf :: CreateSecurityGroupResponse -> ()
rnf CreateSecurityGroupResponse' {Int
Maybe [Tag]
Text
groupId :: Text
httpStatus :: Int
tags :: Maybe [Tag]
$sel:groupId:CreateSecurityGroupResponse' :: CreateSecurityGroupResponse -> Text
$sel:httpStatus:CreateSecurityGroupResponse' :: CreateSecurityGroupResponse -> Int
$sel:tags:CreateSecurityGroupResponse' :: CreateSecurityGroupResponse -> Maybe [Tag]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
groupId