{-# 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.CreateNetworkInterfacePermission
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Grants an Amazon Web Services-authorized account permission to attach
-- the specified network interface to an instance in their account.
--
-- You can grant permission to a single Amazon Web Services account only,
-- and only one account at a time.
module Amazonka.EC2.CreateNetworkInterfacePermission
  ( -- * Creating a Request
    CreateNetworkInterfacePermission (..),
    newCreateNetworkInterfacePermission,

    -- * Request Lenses
    createNetworkInterfacePermission_awsAccountId,
    createNetworkInterfacePermission_awsService,
    createNetworkInterfacePermission_dryRun,
    createNetworkInterfacePermission_networkInterfaceId,
    createNetworkInterfacePermission_permission,

    -- * Destructuring the Response
    CreateNetworkInterfacePermissionResponse (..),
    newCreateNetworkInterfacePermissionResponse,

    -- * Response Lenses
    createNetworkInterfacePermissionResponse_interfacePermission,
    createNetworkInterfacePermissionResponse_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 CreateNetworkInterfacePermission.
--
-- /See:/ 'newCreateNetworkInterfacePermission' smart constructor.
data CreateNetworkInterfacePermission = CreateNetworkInterfacePermission'
  { -- | The Amazon Web Services account ID.
    CreateNetworkInterfacePermission -> Maybe Text
awsAccountId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Service. Currently not supported.
    CreateNetworkInterfacePermission -> Maybe Text
awsService :: Prelude.Maybe Prelude.Text,
    -- | 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@.
    CreateNetworkInterfacePermission -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the network interface.
    CreateNetworkInterfacePermission -> Text
networkInterfaceId :: Prelude.Text,
    -- | The type of permission to grant.
    CreateNetworkInterfacePermission -> InterfacePermissionType
permission :: InterfacePermissionType
  }
  deriving (CreateNetworkInterfacePermission
-> CreateNetworkInterfacePermission -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateNetworkInterfacePermission
-> CreateNetworkInterfacePermission -> Bool
$c/= :: CreateNetworkInterfacePermission
-> CreateNetworkInterfacePermission -> Bool
== :: CreateNetworkInterfacePermission
-> CreateNetworkInterfacePermission -> Bool
$c== :: CreateNetworkInterfacePermission
-> CreateNetworkInterfacePermission -> Bool
Prelude.Eq, ReadPrec [CreateNetworkInterfacePermission]
ReadPrec CreateNetworkInterfacePermission
Int -> ReadS CreateNetworkInterfacePermission
ReadS [CreateNetworkInterfacePermission]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateNetworkInterfacePermission]
$creadListPrec :: ReadPrec [CreateNetworkInterfacePermission]
readPrec :: ReadPrec CreateNetworkInterfacePermission
$creadPrec :: ReadPrec CreateNetworkInterfacePermission
readList :: ReadS [CreateNetworkInterfacePermission]
$creadList :: ReadS [CreateNetworkInterfacePermission]
readsPrec :: Int -> ReadS CreateNetworkInterfacePermission
$creadsPrec :: Int -> ReadS CreateNetworkInterfacePermission
Prelude.Read, Int -> CreateNetworkInterfacePermission -> ShowS
[CreateNetworkInterfacePermission] -> ShowS
CreateNetworkInterfacePermission -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateNetworkInterfacePermission] -> ShowS
$cshowList :: [CreateNetworkInterfacePermission] -> ShowS
show :: CreateNetworkInterfacePermission -> String
$cshow :: CreateNetworkInterfacePermission -> String
showsPrec :: Int -> CreateNetworkInterfacePermission -> ShowS
$cshowsPrec :: Int -> CreateNetworkInterfacePermission -> ShowS
Prelude.Show, forall x.
Rep CreateNetworkInterfacePermission x
-> CreateNetworkInterfacePermission
forall x.
CreateNetworkInterfacePermission
-> Rep CreateNetworkInterfacePermission x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateNetworkInterfacePermission x
-> CreateNetworkInterfacePermission
$cfrom :: forall x.
CreateNetworkInterfacePermission
-> Rep CreateNetworkInterfacePermission x
Prelude.Generic)

-- |
-- Create a value of 'CreateNetworkInterfacePermission' 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:
--
-- 'awsAccountId', 'createNetworkInterfacePermission_awsAccountId' - The Amazon Web Services account ID.
--
-- 'awsService', 'createNetworkInterfacePermission_awsService' - The Amazon Web Service. Currently not supported.
--
-- 'dryRun', 'createNetworkInterfacePermission_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@.
--
-- 'networkInterfaceId', 'createNetworkInterfacePermission_networkInterfaceId' - The ID of the network interface.
--
-- 'permission', 'createNetworkInterfacePermission_permission' - The type of permission to grant.
newCreateNetworkInterfacePermission ::
  -- | 'networkInterfaceId'
  Prelude.Text ->
  -- | 'permission'
  InterfacePermissionType ->
  CreateNetworkInterfacePermission
newCreateNetworkInterfacePermission :: Text -> InterfacePermissionType -> CreateNetworkInterfacePermission
newCreateNetworkInterfacePermission
  Text
pNetworkInterfaceId_
  InterfacePermissionType
pPermission_ =
    CreateNetworkInterfacePermission'
      { $sel:awsAccountId:CreateNetworkInterfacePermission' :: Maybe Text
awsAccountId =
          forall a. Maybe a
Prelude.Nothing,
        $sel:awsService:CreateNetworkInterfacePermission' :: Maybe Text
awsService = forall a. Maybe a
Prelude.Nothing,
        $sel:dryRun:CreateNetworkInterfacePermission' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
        $sel:networkInterfaceId:CreateNetworkInterfacePermission' :: Text
networkInterfaceId = Text
pNetworkInterfaceId_,
        $sel:permission:CreateNetworkInterfacePermission' :: InterfacePermissionType
permission = InterfacePermissionType
pPermission_
      }

-- | The Amazon Web Services account ID.
createNetworkInterfacePermission_awsAccountId :: Lens.Lens' CreateNetworkInterfacePermission (Prelude.Maybe Prelude.Text)
createNetworkInterfacePermission_awsAccountId :: Lens' CreateNetworkInterfacePermission (Maybe Text)
createNetworkInterfacePermission_awsAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNetworkInterfacePermission' {Maybe Text
awsAccountId :: Maybe Text
$sel:awsAccountId:CreateNetworkInterfacePermission' :: CreateNetworkInterfacePermission -> Maybe Text
awsAccountId} -> Maybe Text
awsAccountId) (\s :: CreateNetworkInterfacePermission
s@CreateNetworkInterfacePermission' {} Maybe Text
a -> CreateNetworkInterfacePermission
s {$sel:awsAccountId:CreateNetworkInterfacePermission' :: Maybe Text
awsAccountId = Maybe Text
a} :: CreateNetworkInterfacePermission)

-- | The Amazon Web Service. Currently not supported.
createNetworkInterfacePermission_awsService :: Lens.Lens' CreateNetworkInterfacePermission (Prelude.Maybe Prelude.Text)
createNetworkInterfacePermission_awsService :: Lens' CreateNetworkInterfacePermission (Maybe Text)
createNetworkInterfacePermission_awsService = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNetworkInterfacePermission' {Maybe Text
awsService :: Maybe Text
$sel:awsService:CreateNetworkInterfacePermission' :: CreateNetworkInterfacePermission -> Maybe Text
awsService} -> Maybe Text
awsService) (\s :: CreateNetworkInterfacePermission
s@CreateNetworkInterfacePermission' {} Maybe Text
a -> CreateNetworkInterfacePermission
s {$sel:awsService:CreateNetworkInterfacePermission' :: Maybe Text
awsService = Maybe Text
a} :: CreateNetworkInterfacePermission)

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

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

-- | The type of permission to grant.
createNetworkInterfacePermission_permission :: Lens.Lens' CreateNetworkInterfacePermission InterfacePermissionType
createNetworkInterfacePermission_permission :: Lens' CreateNetworkInterfacePermission InterfacePermissionType
createNetworkInterfacePermission_permission = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNetworkInterfacePermission' {InterfacePermissionType
permission :: InterfacePermissionType
$sel:permission:CreateNetworkInterfacePermission' :: CreateNetworkInterfacePermission -> InterfacePermissionType
permission} -> InterfacePermissionType
permission) (\s :: CreateNetworkInterfacePermission
s@CreateNetworkInterfacePermission' {} InterfacePermissionType
a -> CreateNetworkInterfacePermission
s {$sel:permission:CreateNetworkInterfacePermission' :: InterfacePermissionType
permission = InterfacePermissionType
a} :: CreateNetworkInterfacePermission)

instance
  Core.AWSRequest
    CreateNetworkInterfacePermission
  where
  type
    AWSResponse CreateNetworkInterfacePermission =
      CreateNetworkInterfacePermissionResponse
  request :: (Service -> Service)
-> CreateNetworkInterfacePermission
-> Request CreateNetworkInterfacePermission
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 CreateNetworkInterfacePermission
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse CreateNetworkInterfacePermission)))
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 NetworkInterfacePermission
-> Int -> CreateNetworkInterfacePermissionResponse
CreateNetworkInterfacePermissionResponse'
            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
"interfacePermission")
            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
    CreateNetworkInterfacePermission
  where
  hashWithSalt :: Int -> CreateNetworkInterfacePermission -> Int
hashWithSalt
    Int
_salt
    CreateNetworkInterfacePermission' {Maybe Bool
Maybe Text
Text
InterfacePermissionType
permission :: InterfacePermissionType
networkInterfaceId :: Text
dryRun :: Maybe Bool
awsService :: Maybe Text
awsAccountId :: Maybe Text
$sel:permission:CreateNetworkInterfacePermission' :: CreateNetworkInterfacePermission -> InterfacePermissionType
$sel:networkInterfaceId:CreateNetworkInterfacePermission' :: CreateNetworkInterfacePermission -> Text
$sel:dryRun:CreateNetworkInterfacePermission' :: CreateNetworkInterfacePermission -> Maybe Bool
$sel:awsService:CreateNetworkInterfacePermission' :: CreateNetworkInterfacePermission -> Maybe Text
$sel:awsAccountId:CreateNetworkInterfacePermission' :: CreateNetworkInterfacePermission -> Maybe Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
awsAccountId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
awsService
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
networkInterfaceId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` InterfacePermissionType
permission

instance
  Prelude.NFData
    CreateNetworkInterfacePermission
  where
  rnf :: CreateNetworkInterfacePermission -> ()
rnf CreateNetworkInterfacePermission' {Maybe Bool
Maybe Text
Text
InterfacePermissionType
permission :: InterfacePermissionType
networkInterfaceId :: Text
dryRun :: Maybe Bool
awsService :: Maybe Text
awsAccountId :: Maybe Text
$sel:permission:CreateNetworkInterfacePermission' :: CreateNetworkInterfacePermission -> InterfacePermissionType
$sel:networkInterfaceId:CreateNetworkInterfacePermission' :: CreateNetworkInterfacePermission -> Text
$sel:dryRun:CreateNetworkInterfacePermission' :: CreateNetworkInterfacePermission -> Maybe Bool
$sel:awsService:CreateNetworkInterfacePermission' :: CreateNetworkInterfacePermission -> Maybe Text
$sel:awsAccountId:CreateNetworkInterfacePermission' :: CreateNetworkInterfacePermission -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
awsAccountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
awsService
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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
networkInterfaceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf InterfacePermissionType
permission

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

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

instance
  Data.ToQuery
    CreateNetworkInterfacePermission
  where
  toQuery :: CreateNetworkInterfacePermission -> QueryString
toQuery CreateNetworkInterfacePermission' {Maybe Bool
Maybe Text
Text
InterfacePermissionType
permission :: InterfacePermissionType
networkInterfaceId :: Text
dryRun :: Maybe Bool
awsService :: Maybe Text
awsAccountId :: Maybe Text
$sel:permission:CreateNetworkInterfacePermission' :: CreateNetworkInterfacePermission -> InterfacePermissionType
$sel:networkInterfaceId:CreateNetworkInterfacePermission' :: CreateNetworkInterfacePermission -> Text
$sel:dryRun:CreateNetworkInterfacePermission' :: CreateNetworkInterfacePermission -> Maybe Bool
$sel:awsService:CreateNetworkInterfacePermission' :: CreateNetworkInterfacePermission -> Maybe Text
$sel:awsAccountId:CreateNetworkInterfacePermission' :: CreateNetworkInterfacePermission -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"CreateNetworkInterfacePermission" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"AwsAccountId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
awsAccountId,
        ByteString
"AwsService" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
awsService,
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        ByteString
"NetworkInterfaceId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
networkInterfaceId,
        ByteString
"Permission" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: InterfacePermissionType
permission
      ]

-- | Contains the output of CreateNetworkInterfacePermission.
--
-- /See:/ 'newCreateNetworkInterfacePermissionResponse' smart constructor.
data CreateNetworkInterfacePermissionResponse = CreateNetworkInterfacePermissionResponse'
  { -- | Information about the permission for the network interface.
    CreateNetworkInterfacePermissionResponse
-> Maybe NetworkInterfacePermission
interfacePermission :: Prelude.Maybe NetworkInterfacePermission,
    -- | The response's http status code.
    CreateNetworkInterfacePermissionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateNetworkInterfacePermissionResponse
-> CreateNetworkInterfacePermissionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateNetworkInterfacePermissionResponse
-> CreateNetworkInterfacePermissionResponse -> Bool
$c/= :: CreateNetworkInterfacePermissionResponse
-> CreateNetworkInterfacePermissionResponse -> Bool
== :: CreateNetworkInterfacePermissionResponse
-> CreateNetworkInterfacePermissionResponse -> Bool
$c== :: CreateNetworkInterfacePermissionResponse
-> CreateNetworkInterfacePermissionResponse -> Bool
Prelude.Eq, ReadPrec [CreateNetworkInterfacePermissionResponse]
ReadPrec CreateNetworkInterfacePermissionResponse
Int -> ReadS CreateNetworkInterfacePermissionResponse
ReadS [CreateNetworkInterfacePermissionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateNetworkInterfacePermissionResponse]
$creadListPrec :: ReadPrec [CreateNetworkInterfacePermissionResponse]
readPrec :: ReadPrec CreateNetworkInterfacePermissionResponse
$creadPrec :: ReadPrec CreateNetworkInterfacePermissionResponse
readList :: ReadS [CreateNetworkInterfacePermissionResponse]
$creadList :: ReadS [CreateNetworkInterfacePermissionResponse]
readsPrec :: Int -> ReadS CreateNetworkInterfacePermissionResponse
$creadsPrec :: Int -> ReadS CreateNetworkInterfacePermissionResponse
Prelude.Read, Int -> CreateNetworkInterfacePermissionResponse -> ShowS
[CreateNetworkInterfacePermissionResponse] -> ShowS
CreateNetworkInterfacePermissionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateNetworkInterfacePermissionResponse] -> ShowS
$cshowList :: [CreateNetworkInterfacePermissionResponse] -> ShowS
show :: CreateNetworkInterfacePermissionResponse -> String
$cshow :: CreateNetworkInterfacePermissionResponse -> String
showsPrec :: Int -> CreateNetworkInterfacePermissionResponse -> ShowS
$cshowsPrec :: Int -> CreateNetworkInterfacePermissionResponse -> ShowS
Prelude.Show, forall x.
Rep CreateNetworkInterfacePermissionResponse x
-> CreateNetworkInterfacePermissionResponse
forall x.
CreateNetworkInterfacePermissionResponse
-> Rep CreateNetworkInterfacePermissionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateNetworkInterfacePermissionResponse x
-> CreateNetworkInterfacePermissionResponse
$cfrom :: forall x.
CreateNetworkInterfacePermissionResponse
-> Rep CreateNetworkInterfacePermissionResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateNetworkInterfacePermissionResponse' 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:
--
-- 'interfacePermission', 'createNetworkInterfacePermissionResponse_interfacePermission' - Information about the permission for the network interface.
--
-- 'httpStatus', 'createNetworkInterfacePermissionResponse_httpStatus' - The response's http status code.
newCreateNetworkInterfacePermissionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateNetworkInterfacePermissionResponse
newCreateNetworkInterfacePermissionResponse :: Int -> CreateNetworkInterfacePermissionResponse
newCreateNetworkInterfacePermissionResponse
  Int
pHttpStatus_ =
    CreateNetworkInterfacePermissionResponse'
      { $sel:interfacePermission:CreateNetworkInterfacePermissionResponse' :: Maybe NetworkInterfacePermission
interfacePermission =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:CreateNetworkInterfacePermissionResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | Information about the permission for the network interface.
createNetworkInterfacePermissionResponse_interfacePermission :: Lens.Lens' CreateNetworkInterfacePermissionResponse (Prelude.Maybe NetworkInterfacePermission)
createNetworkInterfacePermissionResponse_interfacePermission :: Lens'
  CreateNetworkInterfacePermissionResponse
  (Maybe NetworkInterfacePermission)
createNetworkInterfacePermissionResponse_interfacePermission = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNetworkInterfacePermissionResponse' {Maybe NetworkInterfacePermission
interfacePermission :: Maybe NetworkInterfacePermission
$sel:interfacePermission:CreateNetworkInterfacePermissionResponse' :: CreateNetworkInterfacePermissionResponse
-> Maybe NetworkInterfacePermission
interfacePermission} -> Maybe NetworkInterfacePermission
interfacePermission) (\s :: CreateNetworkInterfacePermissionResponse
s@CreateNetworkInterfacePermissionResponse' {} Maybe NetworkInterfacePermission
a -> CreateNetworkInterfacePermissionResponse
s {$sel:interfacePermission:CreateNetworkInterfacePermissionResponse' :: Maybe NetworkInterfacePermission
interfacePermission = Maybe NetworkInterfacePermission
a} :: CreateNetworkInterfacePermissionResponse)

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

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