{-# 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.WorkSpaces.DeleteIpGroup
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes the specified IP access control group.
--
-- You cannot delete an IP access control group that is associated with a
-- directory.
module Amazonka.WorkSpaces.DeleteIpGroup
  ( -- * Creating a Request
    DeleteIpGroup (..),
    newDeleteIpGroup,

    -- * Request Lenses
    deleteIpGroup_groupId,

    -- * Destructuring the Response
    DeleteIpGroupResponse (..),
    newDeleteIpGroupResponse,

    -- * Response Lenses
    deleteIpGroupResponse_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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.WorkSpaces.Types

-- | /See:/ 'newDeleteIpGroup' smart constructor.
data DeleteIpGroup = DeleteIpGroup'
  { -- | The identifier of the IP access control group.
    DeleteIpGroup -> Text
groupId :: Prelude.Text
  }
  deriving (DeleteIpGroup -> DeleteIpGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteIpGroup -> DeleteIpGroup -> Bool
$c/= :: DeleteIpGroup -> DeleteIpGroup -> Bool
== :: DeleteIpGroup -> DeleteIpGroup -> Bool
$c== :: DeleteIpGroup -> DeleteIpGroup -> Bool
Prelude.Eq, ReadPrec [DeleteIpGroup]
ReadPrec DeleteIpGroup
Int -> ReadS DeleteIpGroup
ReadS [DeleteIpGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteIpGroup]
$creadListPrec :: ReadPrec [DeleteIpGroup]
readPrec :: ReadPrec DeleteIpGroup
$creadPrec :: ReadPrec DeleteIpGroup
readList :: ReadS [DeleteIpGroup]
$creadList :: ReadS [DeleteIpGroup]
readsPrec :: Int -> ReadS DeleteIpGroup
$creadsPrec :: Int -> ReadS DeleteIpGroup
Prelude.Read, Int -> DeleteIpGroup -> ShowS
[DeleteIpGroup] -> ShowS
DeleteIpGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteIpGroup] -> ShowS
$cshowList :: [DeleteIpGroup] -> ShowS
show :: DeleteIpGroup -> String
$cshow :: DeleteIpGroup -> String
showsPrec :: Int -> DeleteIpGroup -> ShowS
$cshowsPrec :: Int -> DeleteIpGroup -> ShowS
Prelude.Show, forall x. Rep DeleteIpGroup x -> DeleteIpGroup
forall x. DeleteIpGroup -> Rep DeleteIpGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteIpGroup x -> DeleteIpGroup
$cfrom :: forall x. DeleteIpGroup -> Rep DeleteIpGroup x
Prelude.Generic)

-- |
-- Create a value of 'DeleteIpGroup' 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:
--
-- 'groupId', 'deleteIpGroup_groupId' - The identifier of the IP access control group.
newDeleteIpGroup ::
  -- | 'groupId'
  Prelude.Text ->
  DeleteIpGroup
newDeleteIpGroup :: Text -> DeleteIpGroup
newDeleteIpGroup Text
pGroupId_ =
  DeleteIpGroup' {$sel:groupId:DeleteIpGroup' :: Text
groupId = Text
pGroupId_}

-- | The identifier of the IP access control group.
deleteIpGroup_groupId :: Lens.Lens' DeleteIpGroup Prelude.Text
deleteIpGroup_groupId :: Lens' DeleteIpGroup Text
deleteIpGroup_groupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteIpGroup' {Text
groupId :: Text
$sel:groupId:DeleteIpGroup' :: DeleteIpGroup -> Text
groupId} -> Text
groupId) (\s :: DeleteIpGroup
s@DeleteIpGroup' {} Text
a -> DeleteIpGroup
s {$sel:groupId:DeleteIpGroup' :: Text
groupId = Text
a} :: DeleteIpGroup)

instance Core.AWSRequest DeleteIpGroup where
  type
    AWSResponse DeleteIpGroup =
      DeleteIpGroupResponse
  request :: (Service -> Service) -> DeleteIpGroup -> Request DeleteIpGroup
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteIpGroup
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteIpGroup)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> DeleteIpGroupResponse
DeleteIpGroupResponse'
            forall (f :: * -> *) a b. Functor 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 DeleteIpGroup where
  hashWithSalt :: Int -> DeleteIpGroup -> Int
hashWithSalt Int
_salt DeleteIpGroup' {Text
groupId :: Text
$sel:groupId:DeleteIpGroup' :: DeleteIpGroup -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
groupId

instance Prelude.NFData DeleteIpGroup where
  rnf :: DeleteIpGroup -> ()
rnf DeleteIpGroup' {Text
groupId :: Text
$sel:groupId:DeleteIpGroup' :: DeleteIpGroup -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
groupId

instance Data.ToHeaders DeleteIpGroup where
  toHeaders :: DeleteIpGroup -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"WorkspacesService.DeleteIpGroup" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DeleteIpGroup where
  toJSON :: DeleteIpGroup -> Value
toJSON DeleteIpGroup' {Text
groupId :: Text
$sel:groupId:DeleteIpGroup' :: DeleteIpGroup -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"GroupId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
groupId)]
      )

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

instance Data.ToQuery DeleteIpGroup where
  toQuery :: DeleteIpGroup -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

-- |
-- Create a value of 'DeleteIpGroupResponse' 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:
--
-- 'httpStatus', 'deleteIpGroupResponse_httpStatus' - The response's http status code.
newDeleteIpGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteIpGroupResponse
newDeleteIpGroupResponse :: Int -> DeleteIpGroupResponse
newDeleteIpGroupResponse Int
pHttpStatus_ =
  DeleteIpGroupResponse' {$sel:httpStatus:DeleteIpGroupResponse' :: Int
httpStatus = Int
pHttpStatus_}

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

instance Prelude.NFData DeleteIpGroupResponse where
  rnf :: DeleteIpGroupResponse -> ()
rnf DeleteIpGroupResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteIpGroupResponse' :: DeleteIpGroupResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus