{-# 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.DescribeSpotDatafeedSubscription
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describes the data feed for Spot Instances. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/spot-data-feeds.html Spot Instance data feed>
-- in the /Amazon EC2 User Guide for Linux Instances/.
module Amazonka.EC2.DescribeSpotDatafeedSubscription
  ( -- * Creating a Request
    DescribeSpotDatafeedSubscription (..),
    newDescribeSpotDatafeedSubscription,

    -- * Request Lenses
    describeSpotDatafeedSubscription_dryRun,

    -- * Destructuring the Response
    DescribeSpotDatafeedSubscriptionResponse (..),
    newDescribeSpotDatafeedSubscriptionResponse,

    -- * Response Lenses
    describeSpotDatafeedSubscriptionResponse_spotDatafeedSubscription,
    describeSpotDatafeedSubscriptionResponse_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 DescribeSpotDatafeedSubscription.
--
-- /See:/ 'newDescribeSpotDatafeedSubscription' smart constructor.
data DescribeSpotDatafeedSubscription = DescribeSpotDatafeedSubscription'
  { -- | 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@.
    DescribeSpotDatafeedSubscription -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool
  }
  deriving (DescribeSpotDatafeedSubscription
-> DescribeSpotDatafeedSubscription -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeSpotDatafeedSubscription
-> DescribeSpotDatafeedSubscription -> Bool
$c/= :: DescribeSpotDatafeedSubscription
-> DescribeSpotDatafeedSubscription -> Bool
== :: DescribeSpotDatafeedSubscription
-> DescribeSpotDatafeedSubscription -> Bool
$c== :: DescribeSpotDatafeedSubscription
-> DescribeSpotDatafeedSubscription -> Bool
Prelude.Eq, ReadPrec [DescribeSpotDatafeedSubscription]
ReadPrec DescribeSpotDatafeedSubscription
Int -> ReadS DescribeSpotDatafeedSubscription
ReadS [DescribeSpotDatafeedSubscription]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeSpotDatafeedSubscription]
$creadListPrec :: ReadPrec [DescribeSpotDatafeedSubscription]
readPrec :: ReadPrec DescribeSpotDatafeedSubscription
$creadPrec :: ReadPrec DescribeSpotDatafeedSubscription
readList :: ReadS [DescribeSpotDatafeedSubscription]
$creadList :: ReadS [DescribeSpotDatafeedSubscription]
readsPrec :: Int -> ReadS DescribeSpotDatafeedSubscription
$creadsPrec :: Int -> ReadS DescribeSpotDatafeedSubscription
Prelude.Read, Int -> DescribeSpotDatafeedSubscription -> ShowS
[DescribeSpotDatafeedSubscription] -> ShowS
DescribeSpotDatafeedSubscription -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeSpotDatafeedSubscription] -> ShowS
$cshowList :: [DescribeSpotDatafeedSubscription] -> ShowS
show :: DescribeSpotDatafeedSubscription -> String
$cshow :: DescribeSpotDatafeedSubscription -> String
showsPrec :: Int -> DescribeSpotDatafeedSubscription -> ShowS
$cshowsPrec :: Int -> DescribeSpotDatafeedSubscription -> ShowS
Prelude.Show, forall x.
Rep DescribeSpotDatafeedSubscription x
-> DescribeSpotDatafeedSubscription
forall x.
DescribeSpotDatafeedSubscription
-> Rep DescribeSpotDatafeedSubscription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeSpotDatafeedSubscription x
-> DescribeSpotDatafeedSubscription
$cfrom :: forall x.
DescribeSpotDatafeedSubscription
-> Rep DescribeSpotDatafeedSubscription x
Prelude.Generic)

-- |
-- Create a value of 'DescribeSpotDatafeedSubscription' 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', 'describeSpotDatafeedSubscription_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@.
newDescribeSpotDatafeedSubscription ::
  DescribeSpotDatafeedSubscription
newDescribeSpotDatafeedSubscription :: DescribeSpotDatafeedSubscription
newDescribeSpotDatafeedSubscription =
  DescribeSpotDatafeedSubscription'
    { $sel:dryRun:DescribeSpotDatafeedSubscription' :: Maybe Bool
dryRun =
        forall a. Maybe a
Prelude.Nothing
    }

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

instance
  Core.AWSRequest
    DescribeSpotDatafeedSubscription
  where
  type
    AWSResponse DescribeSpotDatafeedSubscription =
      DescribeSpotDatafeedSubscriptionResponse
  request :: (Service -> Service)
-> DescribeSpotDatafeedSubscription
-> Request DescribeSpotDatafeedSubscription
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 DescribeSpotDatafeedSubscription
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse DescribeSpotDatafeedSubscription)))
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 SpotDatafeedSubscription
-> Int -> DescribeSpotDatafeedSubscriptionResponse
DescribeSpotDatafeedSubscriptionResponse'
            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
"spotDatafeedSubscription")
            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
    DescribeSpotDatafeedSubscription
  where
  hashWithSalt :: Int -> DescribeSpotDatafeedSubscription -> Int
hashWithSalt
    Int
_salt
    DescribeSpotDatafeedSubscription' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:DescribeSpotDatafeedSubscription' :: DescribeSpotDatafeedSubscription -> Maybe Bool
..} =
      Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun

instance
  Prelude.NFData
    DescribeSpotDatafeedSubscription
  where
  rnf :: DescribeSpotDatafeedSubscription -> ()
rnf DescribeSpotDatafeedSubscription' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:DescribeSpotDatafeedSubscription' :: DescribeSpotDatafeedSubscription -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dryRun

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

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

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

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

-- |
-- Create a value of 'DescribeSpotDatafeedSubscriptionResponse' 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:
--
-- 'spotDatafeedSubscription', 'describeSpotDatafeedSubscriptionResponse_spotDatafeedSubscription' - The Spot Instance data feed subscription.
--
-- 'httpStatus', 'describeSpotDatafeedSubscriptionResponse_httpStatus' - The response's http status code.
newDescribeSpotDatafeedSubscriptionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeSpotDatafeedSubscriptionResponse
newDescribeSpotDatafeedSubscriptionResponse :: Int -> DescribeSpotDatafeedSubscriptionResponse
newDescribeSpotDatafeedSubscriptionResponse
  Int
pHttpStatus_ =
    DescribeSpotDatafeedSubscriptionResponse'
      { $sel:spotDatafeedSubscription:DescribeSpotDatafeedSubscriptionResponse' :: Maybe SpotDatafeedSubscription
spotDatafeedSubscription =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeSpotDatafeedSubscriptionResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | The Spot Instance data feed subscription.
describeSpotDatafeedSubscriptionResponse_spotDatafeedSubscription :: Lens.Lens' DescribeSpotDatafeedSubscriptionResponse (Prelude.Maybe SpotDatafeedSubscription)
describeSpotDatafeedSubscriptionResponse_spotDatafeedSubscription :: Lens'
  DescribeSpotDatafeedSubscriptionResponse
  (Maybe SpotDatafeedSubscription)
describeSpotDatafeedSubscriptionResponse_spotDatafeedSubscription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSpotDatafeedSubscriptionResponse' {Maybe SpotDatafeedSubscription
spotDatafeedSubscription :: Maybe SpotDatafeedSubscription
$sel:spotDatafeedSubscription:DescribeSpotDatafeedSubscriptionResponse' :: DescribeSpotDatafeedSubscriptionResponse
-> Maybe SpotDatafeedSubscription
spotDatafeedSubscription} -> Maybe SpotDatafeedSubscription
spotDatafeedSubscription) (\s :: DescribeSpotDatafeedSubscriptionResponse
s@DescribeSpotDatafeedSubscriptionResponse' {} Maybe SpotDatafeedSubscription
a -> DescribeSpotDatafeedSubscriptionResponse
s {$sel:spotDatafeedSubscription:DescribeSpotDatafeedSubscriptionResponse' :: Maybe SpotDatafeedSubscription
spotDatafeedSubscription = Maybe SpotDatafeedSubscription
a} :: DescribeSpotDatafeedSubscriptionResponse)

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

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