{-# 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.CancelReservedInstancesListing
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Cancels the specified Reserved Instance listing in the Reserved Instance
-- Marketplace.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/ri-market-general.html Reserved Instance Marketplace>
-- in the /Amazon EC2 User Guide/.
module Amazonka.EC2.CancelReservedInstancesListing
  ( -- * Creating a Request
    CancelReservedInstancesListing (..),
    newCancelReservedInstancesListing,

    -- * Request Lenses
    cancelReservedInstancesListing_reservedInstancesListingId,

    -- * Destructuring the Response
    CancelReservedInstancesListingResponse (..),
    newCancelReservedInstancesListingResponse,

    -- * Response Lenses
    cancelReservedInstancesListingResponse_reservedInstancesListings,
    cancelReservedInstancesListingResponse_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 CancelReservedInstancesListing.
--
-- /See:/ 'newCancelReservedInstancesListing' smart constructor.
data CancelReservedInstancesListing = CancelReservedInstancesListing'
  { -- | The ID of the Reserved Instance listing.
    CancelReservedInstancesListing -> Text
reservedInstancesListingId :: Prelude.Text
  }
  deriving (CancelReservedInstancesListing
-> CancelReservedInstancesListing -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CancelReservedInstancesListing
-> CancelReservedInstancesListing -> Bool
$c/= :: CancelReservedInstancesListing
-> CancelReservedInstancesListing -> Bool
== :: CancelReservedInstancesListing
-> CancelReservedInstancesListing -> Bool
$c== :: CancelReservedInstancesListing
-> CancelReservedInstancesListing -> Bool
Prelude.Eq, ReadPrec [CancelReservedInstancesListing]
ReadPrec CancelReservedInstancesListing
Int -> ReadS CancelReservedInstancesListing
ReadS [CancelReservedInstancesListing]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CancelReservedInstancesListing]
$creadListPrec :: ReadPrec [CancelReservedInstancesListing]
readPrec :: ReadPrec CancelReservedInstancesListing
$creadPrec :: ReadPrec CancelReservedInstancesListing
readList :: ReadS [CancelReservedInstancesListing]
$creadList :: ReadS [CancelReservedInstancesListing]
readsPrec :: Int -> ReadS CancelReservedInstancesListing
$creadsPrec :: Int -> ReadS CancelReservedInstancesListing
Prelude.Read, Int -> CancelReservedInstancesListing -> ShowS
[CancelReservedInstancesListing] -> ShowS
CancelReservedInstancesListing -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CancelReservedInstancesListing] -> ShowS
$cshowList :: [CancelReservedInstancesListing] -> ShowS
show :: CancelReservedInstancesListing -> String
$cshow :: CancelReservedInstancesListing -> String
showsPrec :: Int -> CancelReservedInstancesListing -> ShowS
$cshowsPrec :: Int -> CancelReservedInstancesListing -> ShowS
Prelude.Show, forall x.
Rep CancelReservedInstancesListing x
-> CancelReservedInstancesListing
forall x.
CancelReservedInstancesListing
-> Rep CancelReservedInstancesListing x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CancelReservedInstancesListing x
-> CancelReservedInstancesListing
$cfrom :: forall x.
CancelReservedInstancesListing
-> Rep CancelReservedInstancesListing x
Prelude.Generic)

-- |
-- Create a value of 'CancelReservedInstancesListing' 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:
--
-- 'reservedInstancesListingId', 'cancelReservedInstancesListing_reservedInstancesListingId' - The ID of the Reserved Instance listing.
newCancelReservedInstancesListing ::
  -- | 'reservedInstancesListingId'
  Prelude.Text ->
  CancelReservedInstancesListing
newCancelReservedInstancesListing :: Text -> CancelReservedInstancesListing
newCancelReservedInstancesListing
  Text
pReservedInstancesListingId_ =
    CancelReservedInstancesListing'
      { $sel:reservedInstancesListingId:CancelReservedInstancesListing' :: Text
reservedInstancesListingId =
          Text
pReservedInstancesListingId_
      }

-- | The ID of the Reserved Instance listing.
cancelReservedInstancesListing_reservedInstancesListingId :: Lens.Lens' CancelReservedInstancesListing Prelude.Text
cancelReservedInstancesListing_reservedInstancesListingId :: Lens' CancelReservedInstancesListing Text
cancelReservedInstancesListing_reservedInstancesListingId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelReservedInstancesListing' {Text
reservedInstancesListingId :: Text
$sel:reservedInstancesListingId:CancelReservedInstancesListing' :: CancelReservedInstancesListing -> Text
reservedInstancesListingId} -> Text
reservedInstancesListingId) (\s :: CancelReservedInstancesListing
s@CancelReservedInstancesListing' {} Text
a -> CancelReservedInstancesListing
s {$sel:reservedInstancesListingId:CancelReservedInstancesListing' :: Text
reservedInstancesListingId = Text
a} :: CancelReservedInstancesListing)

instance
  Core.AWSRequest
    CancelReservedInstancesListing
  where
  type
    AWSResponse CancelReservedInstancesListing =
      CancelReservedInstancesListingResponse
  request :: (Service -> Service)
-> CancelReservedInstancesListing
-> Request CancelReservedInstancesListing
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 CancelReservedInstancesListing
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse CancelReservedInstancesListing)))
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 [ReservedInstancesListing]
-> Int -> CancelReservedInstancesListingResponse
CancelReservedInstancesListingResponse'
            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
"reservedInstancesListingsSet"
                            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))
      )

instance
  Prelude.Hashable
    CancelReservedInstancesListing
  where
  hashWithSalt :: Int -> CancelReservedInstancesListing -> Int
hashWithSalt
    Int
_salt
    CancelReservedInstancesListing' {Text
reservedInstancesListingId :: Text
$sel:reservedInstancesListingId:CancelReservedInstancesListing' :: CancelReservedInstancesListing -> Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
reservedInstancesListingId

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

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

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

instance Data.ToQuery CancelReservedInstancesListing where
  toQuery :: CancelReservedInstancesListing -> QueryString
toQuery CancelReservedInstancesListing' {Text
reservedInstancesListingId :: Text
$sel:reservedInstancesListingId:CancelReservedInstancesListing' :: CancelReservedInstancesListing -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"CancelReservedInstancesListing" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"ReservedInstancesListingId"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
reservedInstancesListingId
      ]

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

-- |
-- Create a value of 'CancelReservedInstancesListingResponse' 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:
--
-- 'reservedInstancesListings', 'cancelReservedInstancesListingResponse_reservedInstancesListings' - The Reserved Instance listing.
--
-- 'httpStatus', 'cancelReservedInstancesListingResponse_httpStatus' - The response's http status code.
newCancelReservedInstancesListingResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CancelReservedInstancesListingResponse
newCancelReservedInstancesListingResponse :: Int -> CancelReservedInstancesListingResponse
newCancelReservedInstancesListingResponse
  Int
pHttpStatus_ =
    CancelReservedInstancesListingResponse'
      { $sel:reservedInstancesListings:CancelReservedInstancesListingResponse' :: Maybe [ReservedInstancesListing]
reservedInstancesListings =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:CancelReservedInstancesListingResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | The Reserved Instance listing.
cancelReservedInstancesListingResponse_reservedInstancesListings :: Lens.Lens' CancelReservedInstancesListingResponse (Prelude.Maybe [ReservedInstancesListing])
cancelReservedInstancesListingResponse_reservedInstancesListings :: Lens'
  CancelReservedInstancesListingResponse
  (Maybe [ReservedInstancesListing])
cancelReservedInstancesListingResponse_reservedInstancesListings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelReservedInstancesListingResponse' {Maybe [ReservedInstancesListing]
reservedInstancesListings :: Maybe [ReservedInstancesListing]
$sel:reservedInstancesListings:CancelReservedInstancesListingResponse' :: CancelReservedInstancesListingResponse
-> Maybe [ReservedInstancesListing]
reservedInstancesListings} -> Maybe [ReservedInstancesListing]
reservedInstancesListings) (\s :: CancelReservedInstancesListingResponse
s@CancelReservedInstancesListingResponse' {} Maybe [ReservedInstancesListing]
a -> CancelReservedInstancesListingResponse
s {$sel:reservedInstancesListings:CancelReservedInstancesListingResponse' :: Maybe [ReservedInstancesListing]
reservedInstancesListings = Maybe [ReservedInstancesListing]
a} :: CancelReservedInstancesListingResponse) 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.
cancelReservedInstancesListingResponse_httpStatus :: Lens.Lens' CancelReservedInstancesListingResponse Prelude.Int
cancelReservedInstancesListingResponse_httpStatus :: Lens' CancelReservedInstancesListingResponse Int
cancelReservedInstancesListingResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelReservedInstancesListingResponse' {Int
httpStatus :: Int
$sel:httpStatus:CancelReservedInstancesListingResponse' :: CancelReservedInstancesListingResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: CancelReservedInstancesListingResponse
s@CancelReservedInstancesListingResponse' {} Int
a -> CancelReservedInstancesListingResponse
s {$sel:httpStatus:CancelReservedInstancesListingResponse' :: Int
httpStatus = Int
a} :: CancelReservedInstancesListingResponse)

instance
  Prelude.NFData
    CancelReservedInstancesListingResponse
  where
  rnf :: CancelReservedInstancesListingResponse -> ()
rnf CancelReservedInstancesListingResponse' {Int
Maybe [ReservedInstancesListing]
httpStatus :: Int
reservedInstancesListings :: Maybe [ReservedInstancesListing]
$sel:httpStatus:CancelReservedInstancesListingResponse' :: CancelReservedInstancesListingResponse -> Int
$sel:reservedInstancesListings:CancelReservedInstancesListingResponse' :: CancelReservedInstancesListingResponse
-> Maybe [ReservedInstancesListing]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [ReservedInstancesListing]
reservedInstancesListings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus