{-# 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.IoT.SetLoggingOptions
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Sets the logging options.
--
-- NOTE: use of this command is not recommended. Use @SetV2LoggingOptions@
-- instead.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions SetLoggingOptions>
-- action.
module Amazonka.IoT.SetLoggingOptions
  ( -- * Creating a Request
    SetLoggingOptions (..),
    newSetLoggingOptions,

    -- * Request Lenses
    setLoggingOptions_loggingOptionsPayload,

    -- * Destructuring the Response
    SetLoggingOptionsResponse (..),
    newSetLoggingOptionsResponse,
  )
where

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

-- | The input for the SetLoggingOptions operation.
--
-- /See:/ 'newSetLoggingOptions' smart constructor.
data SetLoggingOptions = SetLoggingOptions'
  { -- | The logging options payload.
    SetLoggingOptions -> LoggingOptionsPayload
loggingOptionsPayload :: LoggingOptionsPayload
  }
  deriving (SetLoggingOptions -> SetLoggingOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetLoggingOptions -> SetLoggingOptions -> Bool
$c/= :: SetLoggingOptions -> SetLoggingOptions -> Bool
== :: SetLoggingOptions -> SetLoggingOptions -> Bool
$c== :: SetLoggingOptions -> SetLoggingOptions -> Bool
Prelude.Eq, ReadPrec [SetLoggingOptions]
ReadPrec SetLoggingOptions
Int -> ReadS SetLoggingOptions
ReadS [SetLoggingOptions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SetLoggingOptions]
$creadListPrec :: ReadPrec [SetLoggingOptions]
readPrec :: ReadPrec SetLoggingOptions
$creadPrec :: ReadPrec SetLoggingOptions
readList :: ReadS [SetLoggingOptions]
$creadList :: ReadS [SetLoggingOptions]
readsPrec :: Int -> ReadS SetLoggingOptions
$creadsPrec :: Int -> ReadS SetLoggingOptions
Prelude.Read, Int -> SetLoggingOptions -> ShowS
[SetLoggingOptions] -> ShowS
SetLoggingOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetLoggingOptions] -> ShowS
$cshowList :: [SetLoggingOptions] -> ShowS
show :: SetLoggingOptions -> String
$cshow :: SetLoggingOptions -> String
showsPrec :: Int -> SetLoggingOptions -> ShowS
$cshowsPrec :: Int -> SetLoggingOptions -> ShowS
Prelude.Show, forall x. Rep SetLoggingOptions x -> SetLoggingOptions
forall x. SetLoggingOptions -> Rep SetLoggingOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetLoggingOptions x -> SetLoggingOptions
$cfrom :: forall x. SetLoggingOptions -> Rep SetLoggingOptions x
Prelude.Generic)

-- |
-- Create a value of 'SetLoggingOptions' 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:
--
-- 'loggingOptionsPayload', 'setLoggingOptions_loggingOptionsPayload' - The logging options payload.
newSetLoggingOptions ::
  -- | 'loggingOptionsPayload'
  LoggingOptionsPayload ->
  SetLoggingOptions
newSetLoggingOptions :: LoggingOptionsPayload -> SetLoggingOptions
newSetLoggingOptions LoggingOptionsPayload
pLoggingOptionsPayload_ =
  SetLoggingOptions'
    { $sel:loggingOptionsPayload:SetLoggingOptions' :: LoggingOptionsPayload
loggingOptionsPayload =
        LoggingOptionsPayload
pLoggingOptionsPayload_
    }

-- | The logging options payload.
setLoggingOptions_loggingOptionsPayload :: Lens.Lens' SetLoggingOptions LoggingOptionsPayload
setLoggingOptions_loggingOptionsPayload :: Lens' SetLoggingOptions LoggingOptionsPayload
setLoggingOptions_loggingOptionsPayload = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SetLoggingOptions' {LoggingOptionsPayload
loggingOptionsPayload :: LoggingOptionsPayload
$sel:loggingOptionsPayload:SetLoggingOptions' :: SetLoggingOptions -> LoggingOptionsPayload
loggingOptionsPayload} -> LoggingOptionsPayload
loggingOptionsPayload) (\s :: SetLoggingOptions
s@SetLoggingOptions' {} LoggingOptionsPayload
a -> SetLoggingOptions
s {$sel:loggingOptionsPayload:SetLoggingOptions' :: LoggingOptionsPayload
loggingOptionsPayload = LoggingOptionsPayload
a} :: SetLoggingOptions)

instance Core.AWSRequest SetLoggingOptions where
  type
    AWSResponse SetLoggingOptions =
      SetLoggingOptionsResponse
  request :: (Service -> Service)
-> SetLoggingOptions -> Request SetLoggingOptions
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 SetLoggingOptions
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse SetLoggingOptions)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull SetLoggingOptionsResponse
SetLoggingOptionsResponse'

instance Prelude.Hashable SetLoggingOptions where
  hashWithSalt :: Int -> SetLoggingOptions -> Int
hashWithSalt Int
_salt SetLoggingOptions' {LoggingOptionsPayload
loggingOptionsPayload :: LoggingOptionsPayload
$sel:loggingOptionsPayload:SetLoggingOptions' :: SetLoggingOptions -> LoggingOptionsPayload
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` LoggingOptionsPayload
loggingOptionsPayload

instance Prelude.NFData SetLoggingOptions where
  rnf :: SetLoggingOptions -> ()
rnf SetLoggingOptions' {LoggingOptionsPayload
loggingOptionsPayload :: LoggingOptionsPayload
$sel:loggingOptionsPayload:SetLoggingOptions' :: SetLoggingOptions -> LoggingOptionsPayload
..} =
    forall a. NFData a => a -> ()
Prelude.rnf LoggingOptionsPayload
loggingOptionsPayload

instance Data.ToHeaders SetLoggingOptions where
  toHeaders :: SetLoggingOptions -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON SetLoggingOptions where
  toJSON :: SetLoggingOptions -> Value
toJSON SetLoggingOptions' {LoggingOptionsPayload
loggingOptionsPayload :: LoggingOptionsPayload
$sel:loggingOptionsPayload:SetLoggingOptions' :: SetLoggingOptions -> LoggingOptionsPayload
..} =
    forall a. ToJSON a => a -> Value
Data.toJSON LoggingOptionsPayload
loggingOptionsPayload

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

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

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

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

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