{-# 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.Shield.DescribeSubscription
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Provides details about the Shield Advanced subscription for an account.
module Amazonka.Shield.DescribeSubscription
  ( -- * Creating a Request
    DescribeSubscription (..),
    newDescribeSubscription,

    -- * Destructuring the Response
    DescribeSubscriptionResponse (..),
    newDescribeSubscriptionResponse,

    -- * Response Lenses
    describeSubscriptionResponse_subscription,
    describeSubscriptionResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.Shield.Types

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

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

instance Core.AWSRequest DescribeSubscription where
  type
    AWSResponse DescribeSubscription =
      DescribeSubscriptionResponse
  request :: (Service -> Service)
-> DescribeSubscription -> Request DescribeSubscription
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeSubscription
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeSubscription)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Subscription -> Int -> DescribeSubscriptionResponse
DescribeSubscriptionResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Subscription")
            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 DescribeSubscription where
  hashWithSalt :: Int -> DescribeSubscription -> Int
hashWithSalt Int
_salt DescribeSubscription
_ =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()

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

instance Data.ToHeaders DescribeSubscription where
  toHeaders :: DescribeSubscription -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AWSShield_20160616.DescribeSubscription" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DescribeSubscription where
  toJSON :: DescribeSubscription -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

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

instance Data.ToQuery DescribeSubscription where
  toQuery :: DescribeSubscription -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newDescribeSubscriptionResponse' smart constructor.
data DescribeSubscriptionResponse = DescribeSubscriptionResponse'
  { -- | The Shield Advanced subscription details for an account.
    DescribeSubscriptionResponse -> Maybe Subscription
subscription :: Prelude.Maybe Subscription,
    -- | The response's http status code.
    DescribeSubscriptionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeSubscriptionResponse
-> DescribeSubscriptionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeSubscriptionResponse
-> DescribeSubscriptionResponse -> Bool
$c/= :: DescribeSubscriptionResponse
-> DescribeSubscriptionResponse -> Bool
== :: DescribeSubscriptionResponse
-> DescribeSubscriptionResponse -> Bool
$c== :: DescribeSubscriptionResponse
-> DescribeSubscriptionResponse -> Bool
Prelude.Eq, ReadPrec [DescribeSubscriptionResponse]
ReadPrec DescribeSubscriptionResponse
Int -> ReadS DescribeSubscriptionResponse
ReadS [DescribeSubscriptionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeSubscriptionResponse]
$creadListPrec :: ReadPrec [DescribeSubscriptionResponse]
readPrec :: ReadPrec DescribeSubscriptionResponse
$creadPrec :: ReadPrec DescribeSubscriptionResponse
readList :: ReadS [DescribeSubscriptionResponse]
$creadList :: ReadS [DescribeSubscriptionResponse]
readsPrec :: Int -> ReadS DescribeSubscriptionResponse
$creadsPrec :: Int -> ReadS DescribeSubscriptionResponse
Prelude.Read, Int -> DescribeSubscriptionResponse -> ShowS
[DescribeSubscriptionResponse] -> ShowS
DescribeSubscriptionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeSubscriptionResponse] -> ShowS
$cshowList :: [DescribeSubscriptionResponse] -> ShowS
show :: DescribeSubscriptionResponse -> String
$cshow :: DescribeSubscriptionResponse -> String
showsPrec :: Int -> DescribeSubscriptionResponse -> ShowS
$cshowsPrec :: Int -> DescribeSubscriptionResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeSubscriptionResponse x -> DescribeSubscriptionResponse
forall x.
DescribeSubscriptionResponse -> Rep DescribeSubscriptionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeSubscriptionResponse x -> DescribeSubscriptionResponse
$cfrom :: forall x.
DescribeSubscriptionResponse -> Rep DescribeSubscriptionResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeSubscriptionResponse' 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:
--
-- 'subscription', 'describeSubscriptionResponse_subscription' - The Shield Advanced subscription details for an account.
--
-- 'httpStatus', 'describeSubscriptionResponse_httpStatus' - The response's http status code.
newDescribeSubscriptionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeSubscriptionResponse
newDescribeSubscriptionResponse :: Int -> DescribeSubscriptionResponse
newDescribeSubscriptionResponse Int
pHttpStatus_ =
  DescribeSubscriptionResponse'
    { $sel:subscription:DescribeSubscriptionResponse' :: Maybe Subscription
subscription =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeSubscriptionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Shield Advanced subscription details for an account.
describeSubscriptionResponse_subscription :: Lens.Lens' DescribeSubscriptionResponse (Prelude.Maybe Subscription)
describeSubscriptionResponse_subscription :: Lens' DescribeSubscriptionResponse (Maybe Subscription)
describeSubscriptionResponse_subscription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSubscriptionResponse' {Maybe Subscription
subscription :: Maybe Subscription
$sel:subscription:DescribeSubscriptionResponse' :: DescribeSubscriptionResponse -> Maybe Subscription
subscription} -> Maybe Subscription
subscription) (\s :: DescribeSubscriptionResponse
s@DescribeSubscriptionResponse' {} Maybe Subscription
a -> DescribeSubscriptionResponse
s {$sel:subscription:DescribeSubscriptionResponse' :: Maybe Subscription
subscription = Maybe Subscription
a} :: DescribeSubscriptionResponse)

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

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