{-# 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.DisableProactiveEngagement
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Removes authorization from the Shield Response Team (SRT) to notify
-- contacts about escalations to the SRT and to initiate proactive customer
-- support.
module Amazonka.Shield.DisableProactiveEngagement
  ( -- * Creating a Request
    DisableProactiveEngagement (..),
    newDisableProactiveEngagement,

    -- * Destructuring the Response
    DisableProactiveEngagementResponse (..),
    newDisableProactiveEngagementResponse,

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

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

instance Core.AWSRequest DisableProactiveEngagement where
  type
    AWSResponse DisableProactiveEngagement =
      DisableProactiveEngagementResponse
  request :: (Service -> Service)
-> DisableProactiveEngagement -> Request DisableProactiveEngagement
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 DisableProactiveEngagement
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DisableProactiveEngagement)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> DisableProactiveEngagementResponse
DisableProactiveEngagementResponse'
            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))
      )

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

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

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

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

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

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

-- |
-- Create a value of 'DisableProactiveEngagementResponse' 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', 'disableProactiveEngagementResponse_httpStatus' - The response's http status code.
newDisableProactiveEngagementResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DisableProactiveEngagementResponse
newDisableProactiveEngagementResponse :: Int -> DisableProactiveEngagementResponse
newDisableProactiveEngagementResponse Int
pHttpStatus_ =
  DisableProactiveEngagementResponse'
    { $sel:httpStatus:DisableProactiveEngagementResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

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

instance
  Prelude.NFData
    DisableProactiveEngagementResponse
  where
  rnf :: DisableProactiveEngagementResponse -> ()
rnf DisableProactiveEngagementResponse' {Int
httpStatus :: Int
$sel:httpStatus:DisableProactiveEngagementResponse' :: DisableProactiveEngagementResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus