{-# 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.UnassignPrivateIpAddresses
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Unassigns one or more secondary private IP addresses, or IPv4 Prefix
-- Delegation prefixes from a network interface.
module Amazonka.EC2.UnassignPrivateIpAddresses
  ( -- * Creating a Request
    UnassignPrivateIpAddresses (..),
    newUnassignPrivateIpAddresses,

    -- * Request Lenses
    unassignPrivateIpAddresses_ipv4Prefixes,
    unassignPrivateIpAddresses_privateIpAddresses,
    unassignPrivateIpAddresses_networkInterfaceId,

    -- * Destructuring the Response
    UnassignPrivateIpAddressesResponse (..),
    newUnassignPrivateIpAddressesResponse,
  )
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 UnassignPrivateIpAddresses.
--
-- /See:/ 'newUnassignPrivateIpAddresses' smart constructor.
data UnassignPrivateIpAddresses = UnassignPrivateIpAddresses'
  { -- | The IPv4 prefixes to unassign from the network interface.
    UnassignPrivateIpAddresses -> Maybe [Text]
ipv4Prefixes :: Prelude.Maybe [Prelude.Text],
    -- | The secondary private IP addresses to unassign from the network
    -- interface. You can specify this option multiple times to unassign more
    -- than one IP address.
    UnassignPrivateIpAddresses -> Maybe [Text]
privateIpAddresses :: Prelude.Maybe [Prelude.Text],
    -- | The ID of the network interface.
    UnassignPrivateIpAddresses -> Text
networkInterfaceId :: Prelude.Text
  }
  deriving (UnassignPrivateIpAddresses -> UnassignPrivateIpAddresses -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnassignPrivateIpAddresses -> UnassignPrivateIpAddresses -> Bool
$c/= :: UnassignPrivateIpAddresses -> UnassignPrivateIpAddresses -> Bool
== :: UnassignPrivateIpAddresses -> UnassignPrivateIpAddresses -> Bool
$c== :: UnassignPrivateIpAddresses -> UnassignPrivateIpAddresses -> Bool
Prelude.Eq, ReadPrec [UnassignPrivateIpAddresses]
ReadPrec UnassignPrivateIpAddresses
Int -> ReadS UnassignPrivateIpAddresses
ReadS [UnassignPrivateIpAddresses]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UnassignPrivateIpAddresses]
$creadListPrec :: ReadPrec [UnassignPrivateIpAddresses]
readPrec :: ReadPrec UnassignPrivateIpAddresses
$creadPrec :: ReadPrec UnassignPrivateIpAddresses
readList :: ReadS [UnassignPrivateIpAddresses]
$creadList :: ReadS [UnassignPrivateIpAddresses]
readsPrec :: Int -> ReadS UnassignPrivateIpAddresses
$creadsPrec :: Int -> ReadS UnassignPrivateIpAddresses
Prelude.Read, Int -> UnassignPrivateIpAddresses -> ShowS
[UnassignPrivateIpAddresses] -> ShowS
UnassignPrivateIpAddresses -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UnassignPrivateIpAddresses] -> ShowS
$cshowList :: [UnassignPrivateIpAddresses] -> ShowS
show :: UnassignPrivateIpAddresses -> String
$cshow :: UnassignPrivateIpAddresses -> String
showsPrec :: Int -> UnassignPrivateIpAddresses -> ShowS
$cshowsPrec :: Int -> UnassignPrivateIpAddresses -> ShowS
Prelude.Show, forall x.
Rep UnassignPrivateIpAddresses x -> UnassignPrivateIpAddresses
forall x.
UnassignPrivateIpAddresses -> Rep UnassignPrivateIpAddresses x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UnassignPrivateIpAddresses x -> UnassignPrivateIpAddresses
$cfrom :: forall x.
UnassignPrivateIpAddresses -> Rep UnassignPrivateIpAddresses x
Prelude.Generic)

-- |
-- Create a value of 'UnassignPrivateIpAddresses' 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:
--
-- 'ipv4Prefixes', 'unassignPrivateIpAddresses_ipv4Prefixes' - The IPv4 prefixes to unassign from the network interface.
--
-- 'privateIpAddresses', 'unassignPrivateIpAddresses_privateIpAddresses' - The secondary private IP addresses to unassign from the network
-- interface. You can specify this option multiple times to unassign more
-- than one IP address.
--
-- 'networkInterfaceId', 'unassignPrivateIpAddresses_networkInterfaceId' - The ID of the network interface.
newUnassignPrivateIpAddresses ::
  -- | 'networkInterfaceId'
  Prelude.Text ->
  UnassignPrivateIpAddresses
newUnassignPrivateIpAddresses :: Text -> UnassignPrivateIpAddresses
newUnassignPrivateIpAddresses Text
pNetworkInterfaceId_ =
  UnassignPrivateIpAddresses'
    { $sel:ipv4Prefixes:UnassignPrivateIpAddresses' :: Maybe [Text]
ipv4Prefixes =
        forall a. Maybe a
Prelude.Nothing,
      $sel:privateIpAddresses:UnassignPrivateIpAddresses' :: Maybe [Text]
privateIpAddresses = forall a. Maybe a
Prelude.Nothing,
      $sel:networkInterfaceId:UnassignPrivateIpAddresses' :: Text
networkInterfaceId = Text
pNetworkInterfaceId_
    }

-- | The IPv4 prefixes to unassign from the network interface.
unassignPrivateIpAddresses_ipv4Prefixes :: Lens.Lens' UnassignPrivateIpAddresses (Prelude.Maybe [Prelude.Text])
unassignPrivateIpAddresses_ipv4Prefixes :: Lens' UnassignPrivateIpAddresses (Maybe [Text])
unassignPrivateIpAddresses_ipv4Prefixes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UnassignPrivateIpAddresses' {Maybe [Text]
ipv4Prefixes :: Maybe [Text]
$sel:ipv4Prefixes:UnassignPrivateIpAddresses' :: UnassignPrivateIpAddresses -> Maybe [Text]
ipv4Prefixes} -> Maybe [Text]
ipv4Prefixes) (\s :: UnassignPrivateIpAddresses
s@UnassignPrivateIpAddresses' {} Maybe [Text]
a -> UnassignPrivateIpAddresses
s {$sel:ipv4Prefixes:UnassignPrivateIpAddresses' :: Maybe [Text]
ipv4Prefixes = Maybe [Text]
a} :: UnassignPrivateIpAddresses) 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 secondary private IP addresses to unassign from the network
-- interface. You can specify this option multiple times to unassign more
-- than one IP address.
unassignPrivateIpAddresses_privateIpAddresses :: Lens.Lens' UnassignPrivateIpAddresses (Prelude.Maybe [Prelude.Text])
unassignPrivateIpAddresses_privateIpAddresses :: Lens' UnassignPrivateIpAddresses (Maybe [Text])
unassignPrivateIpAddresses_privateIpAddresses = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UnassignPrivateIpAddresses' {Maybe [Text]
privateIpAddresses :: Maybe [Text]
$sel:privateIpAddresses:UnassignPrivateIpAddresses' :: UnassignPrivateIpAddresses -> Maybe [Text]
privateIpAddresses} -> Maybe [Text]
privateIpAddresses) (\s :: UnassignPrivateIpAddresses
s@UnassignPrivateIpAddresses' {} Maybe [Text]
a -> UnassignPrivateIpAddresses
s {$sel:privateIpAddresses:UnassignPrivateIpAddresses' :: Maybe [Text]
privateIpAddresses = Maybe [Text]
a} :: UnassignPrivateIpAddresses) 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 ID of the network interface.
unassignPrivateIpAddresses_networkInterfaceId :: Lens.Lens' UnassignPrivateIpAddresses Prelude.Text
unassignPrivateIpAddresses_networkInterfaceId :: Lens' UnassignPrivateIpAddresses Text
unassignPrivateIpAddresses_networkInterfaceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UnassignPrivateIpAddresses' {Text
networkInterfaceId :: Text
$sel:networkInterfaceId:UnassignPrivateIpAddresses' :: UnassignPrivateIpAddresses -> Text
networkInterfaceId} -> Text
networkInterfaceId) (\s :: UnassignPrivateIpAddresses
s@UnassignPrivateIpAddresses' {} Text
a -> UnassignPrivateIpAddresses
s {$sel:networkInterfaceId:UnassignPrivateIpAddresses' :: Text
networkInterfaceId = Text
a} :: UnassignPrivateIpAddresses)

instance Core.AWSRequest UnassignPrivateIpAddresses where
  type
    AWSResponse UnassignPrivateIpAddresses =
      UnassignPrivateIpAddressesResponse
  request :: (Service -> Service)
-> UnassignPrivateIpAddresses -> Request UnassignPrivateIpAddresses
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 UnassignPrivateIpAddresses
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UnassignPrivateIpAddresses)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull
      UnassignPrivateIpAddressesResponse
UnassignPrivateIpAddressesResponse'

instance Prelude.Hashable UnassignPrivateIpAddresses where
  hashWithSalt :: Int -> UnassignPrivateIpAddresses -> Int
hashWithSalt Int
_salt UnassignPrivateIpAddresses' {Maybe [Text]
Text
networkInterfaceId :: Text
privateIpAddresses :: Maybe [Text]
ipv4Prefixes :: Maybe [Text]
$sel:networkInterfaceId:UnassignPrivateIpAddresses' :: UnassignPrivateIpAddresses -> Text
$sel:privateIpAddresses:UnassignPrivateIpAddresses' :: UnassignPrivateIpAddresses -> Maybe [Text]
$sel:ipv4Prefixes:UnassignPrivateIpAddresses' :: UnassignPrivateIpAddresses -> Maybe [Text]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
ipv4Prefixes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
privateIpAddresses
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
networkInterfaceId

instance Prelude.NFData UnassignPrivateIpAddresses where
  rnf :: UnassignPrivateIpAddresses -> ()
rnf UnassignPrivateIpAddresses' {Maybe [Text]
Text
networkInterfaceId :: Text
privateIpAddresses :: Maybe [Text]
ipv4Prefixes :: Maybe [Text]
$sel:networkInterfaceId:UnassignPrivateIpAddresses' :: UnassignPrivateIpAddresses -> Text
$sel:privateIpAddresses:UnassignPrivateIpAddresses' :: UnassignPrivateIpAddresses -> Maybe [Text]
$sel:ipv4Prefixes:UnassignPrivateIpAddresses' :: UnassignPrivateIpAddresses -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
ipv4Prefixes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
privateIpAddresses
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
networkInterfaceId

instance Data.ToHeaders UnassignPrivateIpAddresses where
  toHeaders :: UnassignPrivateIpAddresses -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery UnassignPrivateIpAddresses where
  toQuery :: UnassignPrivateIpAddresses -> QueryString
toQuery UnassignPrivateIpAddresses' {Maybe [Text]
Text
networkInterfaceId :: Text
privateIpAddresses :: Maybe [Text]
ipv4Prefixes :: Maybe [Text]
$sel:networkInterfaceId:UnassignPrivateIpAddresses' :: UnassignPrivateIpAddresses -> Text
$sel:privateIpAddresses:UnassignPrivateIpAddresses' :: UnassignPrivateIpAddresses -> Maybe [Text]
$sel:ipv4Prefixes:UnassignPrivateIpAddresses' :: UnassignPrivateIpAddresses -> Maybe [Text]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"UnassignPrivateIpAddresses" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"Ipv4Prefix"
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
ipv4Prefixes
          ),
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"PrivateIpAddress"
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
privateIpAddresses
          ),
        ByteString
"NetworkInterfaceId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
networkInterfaceId
      ]

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

-- |
-- Create a value of 'UnassignPrivateIpAddressesResponse' 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.
newUnassignPrivateIpAddressesResponse ::
  UnassignPrivateIpAddressesResponse
newUnassignPrivateIpAddressesResponse :: UnassignPrivateIpAddressesResponse
newUnassignPrivateIpAddressesResponse =
  UnassignPrivateIpAddressesResponse
UnassignPrivateIpAddressesResponse'

instance
  Prelude.NFData
    UnassignPrivateIpAddressesResponse
  where
  rnf :: UnassignPrivateIpAddressesResponse -> ()
rnf UnassignPrivateIpAddressesResponse
_ = ()