{-# 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.IoTEvents.PutLoggingOptions
-- 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 or updates the AWS IoT Events logging options.
--
-- If you update the value of any @loggingOptions@ field, it takes up to
-- one minute for the change to take effect. If you change the policy
-- attached to the role you specified in the @roleArn@ field (for example,
-- to correct an invalid policy), it takes up to five minutes for that
-- change to take effect.
module Amazonka.IoTEvents.PutLoggingOptions
  ( -- * Creating a Request
    PutLoggingOptions (..),
    newPutLoggingOptions,

    -- * Request Lenses
    putLoggingOptions_loggingOptions,

    -- * Destructuring the Response
    PutLoggingOptionsResponse (..),
    newPutLoggingOptionsResponse,
  )
where

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

-- | /See:/ 'newPutLoggingOptions' smart constructor.
data PutLoggingOptions = PutLoggingOptions'
  { -- | The new values of the AWS IoT Events logging options.
    PutLoggingOptions -> LoggingOptions
loggingOptions :: LoggingOptions
  }
  deriving (PutLoggingOptions -> PutLoggingOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutLoggingOptions -> PutLoggingOptions -> Bool
$c/= :: PutLoggingOptions -> PutLoggingOptions -> Bool
== :: PutLoggingOptions -> PutLoggingOptions -> Bool
$c== :: PutLoggingOptions -> PutLoggingOptions -> Bool
Prelude.Eq, ReadPrec [PutLoggingOptions]
ReadPrec PutLoggingOptions
Int -> ReadS PutLoggingOptions
ReadS [PutLoggingOptions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutLoggingOptions]
$creadListPrec :: ReadPrec [PutLoggingOptions]
readPrec :: ReadPrec PutLoggingOptions
$creadPrec :: ReadPrec PutLoggingOptions
readList :: ReadS [PutLoggingOptions]
$creadList :: ReadS [PutLoggingOptions]
readsPrec :: Int -> ReadS PutLoggingOptions
$creadsPrec :: Int -> ReadS PutLoggingOptions
Prelude.Read, Int -> PutLoggingOptions -> ShowS
[PutLoggingOptions] -> ShowS
PutLoggingOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutLoggingOptions] -> ShowS
$cshowList :: [PutLoggingOptions] -> ShowS
show :: PutLoggingOptions -> String
$cshow :: PutLoggingOptions -> String
showsPrec :: Int -> PutLoggingOptions -> ShowS
$cshowsPrec :: Int -> PutLoggingOptions -> ShowS
Prelude.Show, forall x. Rep PutLoggingOptions x -> PutLoggingOptions
forall x. PutLoggingOptions -> Rep PutLoggingOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutLoggingOptions x -> PutLoggingOptions
$cfrom :: forall x. PutLoggingOptions -> Rep PutLoggingOptions x
Prelude.Generic)

-- |
-- Create a value of 'PutLoggingOptions' 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:
--
-- 'loggingOptions', 'putLoggingOptions_loggingOptions' - The new values of the AWS IoT Events logging options.
newPutLoggingOptions ::
  -- | 'loggingOptions'
  LoggingOptions ->
  PutLoggingOptions
newPutLoggingOptions :: LoggingOptions -> PutLoggingOptions
newPutLoggingOptions LoggingOptions
pLoggingOptions_ =
  PutLoggingOptions'
    { $sel:loggingOptions:PutLoggingOptions' :: LoggingOptions
loggingOptions =
        LoggingOptions
pLoggingOptions_
    }

-- | The new values of the AWS IoT Events logging options.
putLoggingOptions_loggingOptions :: Lens.Lens' PutLoggingOptions LoggingOptions
putLoggingOptions_loggingOptions :: Lens' PutLoggingOptions LoggingOptions
putLoggingOptions_loggingOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutLoggingOptions' {LoggingOptions
loggingOptions :: LoggingOptions
$sel:loggingOptions:PutLoggingOptions' :: PutLoggingOptions -> LoggingOptions
loggingOptions} -> LoggingOptions
loggingOptions) (\s :: PutLoggingOptions
s@PutLoggingOptions' {} LoggingOptions
a -> PutLoggingOptions
s {$sel:loggingOptions:PutLoggingOptions' :: LoggingOptions
loggingOptions = LoggingOptions
a} :: PutLoggingOptions)

instance Core.AWSRequest PutLoggingOptions where
  type
    AWSResponse PutLoggingOptions =
      PutLoggingOptionsResponse
  request :: (Service -> Service)
-> PutLoggingOptions -> Request PutLoggingOptions
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy PutLoggingOptions
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse PutLoggingOptions)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull PutLoggingOptionsResponse
PutLoggingOptionsResponse'

instance Prelude.Hashable PutLoggingOptions where
  hashWithSalt :: Int -> PutLoggingOptions -> Int
hashWithSalt Int
_salt PutLoggingOptions' {LoggingOptions
loggingOptions :: LoggingOptions
$sel:loggingOptions:PutLoggingOptions' :: PutLoggingOptions -> LoggingOptions
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` LoggingOptions
loggingOptions

instance Prelude.NFData PutLoggingOptions where
  rnf :: PutLoggingOptions -> ()
rnf PutLoggingOptions' {LoggingOptions
loggingOptions :: LoggingOptions
$sel:loggingOptions:PutLoggingOptions' :: PutLoggingOptions -> LoggingOptions
..} =
    forall a. NFData a => a -> ()
Prelude.rnf LoggingOptions
loggingOptions

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

instance Data.ToJSON PutLoggingOptions where
  toJSON :: PutLoggingOptions -> Value
toJSON PutLoggingOptions' {LoggingOptions
loggingOptions :: LoggingOptions
$sel:loggingOptions:PutLoggingOptions' :: PutLoggingOptions -> LoggingOptions
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"loggingOptions" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= LoggingOptions
loggingOptions)
          ]
      )

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

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

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

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

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