{-# 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.GetSubscriptionState
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns the @SubscriptionState@, either @Active@ or @Inactive@.
module Amazonka.Shield.GetSubscriptionState
  ( -- * Creating a Request
    GetSubscriptionState (..),
    newGetSubscriptionState,

    -- * Destructuring the Response
    GetSubscriptionStateResponse (..),
    newGetSubscriptionStateResponse,

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

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

instance Core.AWSRequest GetSubscriptionState where
  type
    AWSResponse GetSubscriptionState =
      GetSubscriptionStateResponse
  request :: (Service -> Service)
-> GetSubscriptionState -> Request GetSubscriptionState
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 GetSubscriptionState
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetSubscriptionState)))
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 ->
          Int -> SubscriptionState -> GetSubscriptionStateResponse
GetSubscriptionStateResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"SubscriptionState")
      )

instance Prelude.Hashable GetSubscriptionState where
  hashWithSalt :: Int -> GetSubscriptionState -> Int
hashWithSalt Int
_salt GetSubscriptionState
_ =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()

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

instance Data.ToHeaders GetSubscriptionState where
  toHeaders :: GetSubscriptionState -> 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.GetSubscriptionState" ::
                          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 GetSubscriptionState where
  toJSON :: GetSubscriptionState -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

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

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

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

-- |
-- Create a value of 'GetSubscriptionStateResponse' 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:
--
-- 'httpStatus', 'getSubscriptionStateResponse_httpStatus' - The response's http status code.
--
-- 'subscriptionState', 'getSubscriptionStateResponse_subscriptionState' - The status of the subscription.
newGetSubscriptionStateResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'subscriptionState'
  SubscriptionState ->
  GetSubscriptionStateResponse
newGetSubscriptionStateResponse :: Int -> SubscriptionState -> GetSubscriptionStateResponse
newGetSubscriptionStateResponse
  Int
pHttpStatus_
  SubscriptionState
pSubscriptionState_ =
    GetSubscriptionStateResponse'
      { $sel:httpStatus:GetSubscriptionStateResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:subscriptionState:GetSubscriptionStateResponse' :: SubscriptionState
subscriptionState = SubscriptionState
pSubscriptionState_
      }

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

-- | The status of the subscription.
getSubscriptionStateResponse_subscriptionState :: Lens.Lens' GetSubscriptionStateResponse SubscriptionState
getSubscriptionStateResponse_subscriptionState :: Lens' GetSubscriptionStateResponse SubscriptionState
getSubscriptionStateResponse_subscriptionState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSubscriptionStateResponse' {SubscriptionState
subscriptionState :: SubscriptionState
$sel:subscriptionState:GetSubscriptionStateResponse' :: GetSubscriptionStateResponse -> SubscriptionState
subscriptionState} -> SubscriptionState
subscriptionState) (\s :: GetSubscriptionStateResponse
s@GetSubscriptionStateResponse' {} SubscriptionState
a -> GetSubscriptionStateResponse
s {$sel:subscriptionState:GetSubscriptionStateResponse' :: SubscriptionState
subscriptionState = SubscriptionState
a} :: GetSubscriptionStateResponse)

instance Prelude.NFData GetSubscriptionStateResponse where
  rnf :: GetSubscriptionStateResponse -> ()
rnf GetSubscriptionStateResponse' {Int
SubscriptionState
subscriptionState :: SubscriptionState
httpStatus :: Int
$sel:subscriptionState:GetSubscriptionStateResponse' :: GetSubscriptionStateResponse -> SubscriptionState
$sel:httpStatus:GetSubscriptionStateResponse' :: GetSubscriptionStateResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf SubscriptionState
subscriptionState