{-# 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.IoTWireless.ResetAllResourceLogLevels
-- 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 the log-level overrides for all resources; both wireless devices
-- and wireless gateways.
module Amazonka.IoTWireless.ResetAllResourceLogLevels
  ( -- * Creating a Request
    ResetAllResourceLogLevels (..),
    newResetAllResourceLogLevels,

    -- * Destructuring the Response
    ResetAllResourceLogLevelsResponse (..),
    newResetAllResourceLogLevelsResponse,

    -- * Response Lenses
    resetAllResourceLogLevelsResponse_httpStatus,
  )
where

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

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

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

instance Core.AWSRequest ResetAllResourceLogLevels where
  type
    AWSResponse ResetAllResourceLogLevels =
      ResetAllResourceLogLevelsResponse
  request :: (Service -> Service)
-> ResetAllResourceLogLevels -> Request ResetAllResourceLogLevels
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ResetAllResourceLogLevels
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ResetAllResourceLogLevels)))
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 -> ResetAllResourceLogLevelsResponse
ResetAllResourceLogLevelsResponse'
            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 ResetAllResourceLogLevels where
  hashWithSalt :: Int -> ResetAllResourceLogLevels -> Int
hashWithSalt Int
_salt ResetAllResourceLogLevels
_ =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()

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

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

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

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

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

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

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

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