{-# 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.DeleteNetworkInterfacePermission
-- 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 a permission for a network interface. By default, you cannot
-- delete the permission if the account for which you\'re removing the
-- permission has attached the network interface to an instance. However,
-- you can force delete the permission, regardless of any attachment.
module Amazonka.EC2.DeleteNetworkInterfacePermission
  ( -- * Creating a Request
    DeleteNetworkInterfacePermission (..),
    newDeleteNetworkInterfacePermission,

    -- * Request Lenses
    deleteNetworkInterfacePermission_dryRun,
    deleteNetworkInterfacePermission_force,
    deleteNetworkInterfacePermission_networkInterfacePermissionId,

    -- * Destructuring the Response
    DeleteNetworkInterfacePermissionResponse (..),
    newDeleteNetworkInterfacePermissionResponse,

    -- * Response Lenses
    deleteNetworkInterfacePermissionResponse_return,
    deleteNetworkInterfacePermissionResponse_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

-- | Contains the parameters for DeleteNetworkInterfacePermission.
--
-- /See:/ 'newDeleteNetworkInterfacePermission' smart constructor.
data DeleteNetworkInterfacePermission = DeleteNetworkInterfacePermission'
  { -- | 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@.
    DeleteNetworkInterfacePermission -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | Specify @true@ to remove the permission even if the network interface is
    -- attached to an instance.
    DeleteNetworkInterfacePermission -> Maybe Bool
force :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the network interface permission.
    DeleteNetworkInterfacePermission -> Text
networkInterfacePermissionId :: Prelude.Text
  }
  deriving (DeleteNetworkInterfacePermission
-> DeleteNetworkInterfacePermission -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteNetworkInterfacePermission
-> DeleteNetworkInterfacePermission -> Bool
$c/= :: DeleteNetworkInterfacePermission
-> DeleteNetworkInterfacePermission -> Bool
== :: DeleteNetworkInterfacePermission
-> DeleteNetworkInterfacePermission -> Bool
$c== :: DeleteNetworkInterfacePermission
-> DeleteNetworkInterfacePermission -> Bool
Prelude.Eq, ReadPrec [DeleteNetworkInterfacePermission]
ReadPrec DeleteNetworkInterfacePermission
Int -> ReadS DeleteNetworkInterfacePermission
ReadS [DeleteNetworkInterfacePermission]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteNetworkInterfacePermission]
$creadListPrec :: ReadPrec [DeleteNetworkInterfacePermission]
readPrec :: ReadPrec DeleteNetworkInterfacePermission
$creadPrec :: ReadPrec DeleteNetworkInterfacePermission
readList :: ReadS [DeleteNetworkInterfacePermission]
$creadList :: ReadS [DeleteNetworkInterfacePermission]
readsPrec :: Int -> ReadS DeleteNetworkInterfacePermission
$creadsPrec :: Int -> ReadS DeleteNetworkInterfacePermission
Prelude.Read, Int -> DeleteNetworkInterfacePermission -> ShowS
[DeleteNetworkInterfacePermission] -> ShowS
DeleteNetworkInterfacePermission -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteNetworkInterfacePermission] -> ShowS
$cshowList :: [DeleteNetworkInterfacePermission] -> ShowS
show :: DeleteNetworkInterfacePermission -> String
$cshow :: DeleteNetworkInterfacePermission -> String
showsPrec :: Int -> DeleteNetworkInterfacePermission -> ShowS
$cshowsPrec :: Int -> DeleteNetworkInterfacePermission -> ShowS
Prelude.Show, forall x.
Rep DeleteNetworkInterfacePermission x
-> DeleteNetworkInterfacePermission
forall x.
DeleteNetworkInterfacePermission
-> Rep DeleteNetworkInterfacePermission x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteNetworkInterfacePermission x
-> DeleteNetworkInterfacePermission
$cfrom :: forall x.
DeleteNetworkInterfacePermission
-> Rep DeleteNetworkInterfacePermission x
Prelude.Generic)

-- |
-- Create a value of 'DeleteNetworkInterfacePermission' 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', 'deleteNetworkInterfacePermission_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@.
--
-- 'force', 'deleteNetworkInterfacePermission_force' - Specify @true@ to remove the permission even if the network interface is
-- attached to an instance.
--
-- 'networkInterfacePermissionId', 'deleteNetworkInterfacePermission_networkInterfacePermissionId' - The ID of the network interface permission.
newDeleteNetworkInterfacePermission ::
  -- | 'networkInterfacePermissionId'
  Prelude.Text ->
  DeleteNetworkInterfacePermission
newDeleteNetworkInterfacePermission :: Text -> DeleteNetworkInterfacePermission
newDeleteNetworkInterfacePermission
  Text
pNetworkInterfacePermissionId_ =
    DeleteNetworkInterfacePermission'
      { $sel:dryRun:DeleteNetworkInterfacePermission' :: Maybe Bool
dryRun =
          forall a. Maybe a
Prelude.Nothing,
        $sel:force:DeleteNetworkInterfacePermission' :: Maybe Bool
force = forall a. Maybe a
Prelude.Nothing,
        $sel:networkInterfacePermissionId:DeleteNetworkInterfacePermission' :: Text
networkInterfacePermissionId =
          Text
pNetworkInterfacePermissionId_
      }

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

-- | Specify @true@ to remove the permission even if the network interface is
-- attached to an instance.
deleteNetworkInterfacePermission_force :: Lens.Lens' DeleteNetworkInterfacePermission (Prelude.Maybe Prelude.Bool)
deleteNetworkInterfacePermission_force :: Lens' DeleteNetworkInterfacePermission (Maybe Bool)
deleteNetworkInterfacePermission_force = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteNetworkInterfacePermission' {Maybe Bool
force :: Maybe Bool
$sel:force:DeleteNetworkInterfacePermission' :: DeleteNetworkInterfacePermission -> Maybe Bool
force} -> Maybe Bool
force) (\s :: DeleteNetworkInterfacePermission
s@DeleteNetworkInterfacePermission' {} Maybe Bool
a -> DeleteNetworkInterfacePermission
s {$sel:force:DeleteNetworkInterfacePermission' :: Maybe Bool
force = Maybe Bool
a} :: DeleteNetworkInterfacePermission)

-- | The ID of the network interface permission.
deleteNetworkInterfacePermission_networkInterfacePermissionId :: Lens.Lens' DeleteNetworkInterfacePermission Prelude.Text
deleteNetworkInterfacePermission_networkInterfacePermissionId :: Lens' DeleteNetworkInterfacePermission Text
deleteNetworkInterfacePermission_networkInterfacePermissionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteNetworkInterfacePermission' {Text
networkInterfacePermissionId :: Text
$sel:networkInterfacePermissionId:DeleteNetworkInterfacePermission' :: DeleteNetworkInterfacePermission -> Text
networkInterfacePermissionId} -> Text
networkInterfacePermissionId) (\s :: DeleteNetworkInterfacePermission
s@DeleteNetworkInterfacePermission' {} Text
a -> DeleteNetworkInterfacePermission
s {$sel:networkInterfacePermissionId:DeleteNetworkInterfacePermission' :: Text
networkInterfacePermissionId = Text
a} :: DeleteNetworkInterfacePermission)

instance
  Core.AWSRequest
    DeleteNetworkInterfacePermission
  where
  type
    AWSResponse DeleteNetworkInterfacePermission =
      DeleteNetworkInterfacePermissionResponse
  request :: (Service -> Service)
-> DeleteNetworkInterfacePermission
-> Request DeleteNetworkInterfacePermission
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 DeleteNetworkInterfacePermission
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse DeleteNetworkInterfacePermission)))
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 -> DeleteNetworkInterfacePermissionResponse
DeleteNetworkInterfacePermissionResponse'
            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
    DeleteNetworkInterfacePermission
  where
  hashWithSalt :: Int -> DeleteNetworkInterfacePermission -> Int
hashWithSalt
    Int
_salt
    DeleteNetworkInterfacePermission' {Maybe Bool
Text
networkInterfacePermissionId :: Text
force :: Maybe Bool
dryRun :: Maybe Bool
$sel:networkInterfacePermissionId:DeleteNetworkInterfacePermission' :: DeleteNetworkInterfacePermission -> Text
$sel:force:DeleteNetworkInterfacePermission' :: DeleteNetworkInterfacePermission -> Maybe Bool
$sel:dryRun:DeleteNetworkInterfacePermission' :: DeleteNetworkInterfacePermission -> 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 Bool
force
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
networkInterfacePermissionId

instance
  Prelude.NFData
    DeleteNetworkInterfacePermission
  where
  rnf :: DeleteNetworkInterfacePermission -> ()
rnf DeleteNetworkInterfacePermission' {Maybe Bool
Text
networkInterfacePermissionId :: Text
force :: Maybe Bool
dryRun :: Maybe Bool
$sel:networkInterfacePermissionId:DeleteNetworkInterfacePermission' :: DeleteNetworkInterfacePermission -> Text
$sel:force:DeleteNetworkInterfacePermission' :: DeleteNetworkInterfacePermission -> Maybe Bool
$sel:dryRun:DeleteNetworkInterfacePermission' :: DeleteNetworkInterfacePermission -> 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 Bool
force
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
networkInterfacePermissionId

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

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

instance
  Data.ToQuery
    DeleteNetworkInterfacePermission
  where
  toQuery :: DeleteNetworkInterfacePermission -> QueryString
toQuery DeleteNetworkInterfacePermission' {Maybe Bool
Text
networkInterfacePermissionId :: Text
force :: Maybe Bool
dryRun :: Maybe Bool
$sel:networkInterfacePermissionId:DeleteNetworkInterfacePermission' :: DeleteNetworkInterfacePermission -> Text
$sel:force:DeleteNetworkInterfacePermission' :: DeleteNetworkInterfacePermission -> Maybe Bool
$sel:dryRun:DeleteNetworkInterfacePermission' :: DeleteNetworkInterfacePermission -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"DeleteNetworkInterfacePermission" ::
                      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
"Force" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
force,
        ByteString
"NetworkInterfacePermissionId"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
networkInterfacePermissionId
      ]

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

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

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

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

instance
  Prelude.NFData
    DeleteNetworkInterfacePermissionResponse
  where
  rnf :: DeleteNetworkInterfacePermissionResponse -> ()
rnf DeleteNetworkInterfacePermissionResponse' {Int
Maybe Bool
httpStatus :: Int
return' :: Maybe Bool
$sel:httpStatus:DeleteNetworkInterfacePermissionResponse' :: DeleteNetworkInterfacePermissionResponse -> Int
$sel:return':DeleteNetworkInterfacePermissionResponse' :: DeleteNetworkInterfacePermissionResponse -> 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