{-# 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.IoTEventsData.BatchAcknowledgeAlarm
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Acknowledges one or more alarms. The alarms change to the @ACKNOWLEDGED@
-- state after you acknowledge them.
module Amazonka.IoTEventsData.BatchAcknowledgeAlarm
  ( -- * Creating a Request
    BatchAcknowledgeAlarm (..),
    newBatchAcknowledgeAlarm,

    -- * Request Lenses
    batchAcknowledgeAlarm_acknowledgeActionRequests,

    -- * Destructuring the Response
    BatchAcknowledgeAlarmResponse (..),
    newBatchAcknowledgeAlarmResponse,

    -- * Response Lenses
    batchAcknowledgeAlarmResponse_errorEntries,
    batchAcknowledgeAlarmResponse_httpStatus,
  )
where

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

-- | /See:/ 'newBatchAcknowledgeAlarm' smart constructor.
data BatchAcknowledgeAlarm = BatchAcknowledgeAlarm'
  { -- | The list of acknowledge action requests. You can specify up to 10
    -- requests per operation.
    BatchAcknowledgeAlarm -> NonEmpty AcknowledgeAlarmActionRequest
acknowledgeActionRequests :: Prelude.NonEmpty AcknowledgeAlarmActionRequest
  }
  deriving (BatchAcknowledgeAlarm -> BatchAcknowledgeAlarm -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchAcknowledgeAlarm -> BatchAcknowledgeAlarm -> Bool
$c/= :: BatchAcknowledgeAlarm -> BatchAcknowledgeAlarm -> Bool
== :: BatchAcknowledgeAlarm -> BatchAcknowledgeAlarm -> Bool
$c== :: BatchAcknowledgeAlarm -> BatchAcknowledgeAlarm -> Bool
Prelude.Eq, ReadPrec [BatchAcknowledgeAlarm]
ReadPrec BatchAcknowledgeAlarm
Int -> ReadS BatchAcknowledgeAlarm
ReadS [BatchAcknowledgeAlarm]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchAcknowledgeAlarm]
$creadListPrec :: ReadPrec [BatchAcknowledgeAlarm]
readPrec :: ReadPrec BatchAcknowledgeAlarm
$creadPrec :: ReadPrec BatchAcknowledgeAlarm
readList :: ReadS [BatchAcknowledgeAlarm]
$creadList :: ReadS [BatchAcknowledgeAlarm]
readsPrec :: Int -> ReadS BatchAcknowledgeAlarm
$creadsPrec :: Int -> ReadS BatchAcknowledgeAlarm
Prelude.Read, Int -> BatchAcknowledgeAlarm -> ShowS
[BatchAcknowledgeAlarm] -> ShowS
BatchAcknowledgeAlarm -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchAcknowledgeAlarm] -> ShowS
$cshowList :: [BatchAcknowledgeAlarm] -> ShowS
show :: BatchAcknowledgeAlarm -> String
$cshow :: BatchAcknowledgeAlarm -> String
showsPrec :: Int -> BatchAcknowledgeAlarm -> ShowS
$cshowsPrec :: Int -> BatchAcknowledgeAlarm -> ShowS
Prelude.Show, forall x. Rep BatchAcknowledgeAlarm x -> BatchAcknowledgeAlarm
forall x. BatchAcknowledgeAlarm -> Rep BatchAcknowledgeAlarm x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BatchAcknowledgeAlarm x -> BatchAcknowledgeAlarm
$cfrom :: forall x. BatchAcknowledgeAlarm -> Rep BatchAcknowledgeAlarm x
Prelude.Generic)

-- |
-- Create a value of 'BatchAcknowledgeAlarm' 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:
--
-- 'acknowledgeActionRequests', 'batchAcknowledgeAlarm_acknowledgeActionRequests' - The list of acknowledge action requests. You can specify up to 10
-- requests per operation.
newBatchAcknowledgeAlarm ::
  -- | 'acknowledgeActionRequests'
  Prelude.NonEmpty AcknowledgeAlarmActionRequest ->
  BatchAcknowledgeAlarm
newBatchAcknowledgeAlarm :: NonEmpty AcknowledgeAlarmActionRequest -> BatchAcknowledgeAlarm
newBatchAcknowledgeAlarm NonEmpty AcknowledgeAlarmActionRequest
pAcknowledgeActionRequests_ =
  BatchAcknowledgeAlarm'
    { $sel:acknowledgeActionRequests:BatchAcknowledgeAlarm' :: NonEmpty AcknowledgeAlarmActionRequest
acknowledgeActionRequests =
        forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty AcknowledgeAlarmActionRequest
pAcknowledgeActionRequests_
    }

-- | The list of acknowledge action requests. You can specify up to 10
-- requests per operation.
batchAcknowledgeAlarm_acknowledgeActionRequests :: Lens.Lens' BatchAcknowledgeAlarm (Prelude.NonEmpty AcknowledgeAlarmActionRequest)
batchAcknowledgeAlarm_acknowledgeActionRequests :: Lens'
  BatchAcknowledgeAlarm (NonEmpty AcknowledgeAlarmActionRequest)
batchAcknowledgeAlarm_acknowledgeActionRequests = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchAcknowledgeAlarm' {NonEmpty AcknowledgeAlarmActionRequest
acknowledgeActionRequests :: NonEmpty AcknowledgeAlarmActionRequest
$sel:acknowledgeActionRequests:BatchAcknowledgeAlarm' :: BatchAcknowledgeAlarm -> NonEmpty AcknowledgeAlarmActionRequest
acknowledgeActionRequests} -> NonEmpty AcknowledgeAlarmActionRequest
acknowledgeActionRequests) (\s :: BatchAcknowledgeAlarm
s@BatchAcknowledgeAlarm' {} NonEmpty AcknowledgeAlarmActionRequest
a -> BatchAcknowledgeAlarm
s {$sel:acknowledgeActionRequests:BatchAcknowledgeAlarm' :: NonEmpty AcknowledgeAlarmActionRequest
acknowledgeActionRequests = NonEmpty AcknowledgeAlarmActionRequest
a} :: BatchAcknowledgeAlarm) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest BatchAcknowledgeAlarm where
  type
    AWSResponse BatchAcknowledgeAlarm =
      BatchAcknowledgeAlarmResponse
  request :: (Service -> Service)
-> BatchAcknowledgeAlarm -> Request BatchAcknowledgeAlarm
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 BatchAcknowledgeAlarm
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse BatchAcknowledgeAlarm)))
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 ->
          Maybe [BatchAlarmActionErrorEntry]
-> Int -> BatchAcknowledgeAlarmResponse
BatchAcknowledgeAlarmResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"errorEntries" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => 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 BatchAcknowledgeAlarm where
  hashWithSalt :: Int -> BatchAcknowledgeAlarm -> Int
hashWithSalt Int
_salt BatchAcknowledgeAlarm' {NonEmpty AcknowledgeAlarmActionRequest
acknowledgeActionRequests :: NonEmpty AcknowledgeAlarmActionRequest
$sel:acknowledgeActionRequests:BatchAcknowledgeAlarm' :: BatchAcknowledgeAlarm -> NonEmpty AcknowledgeAlarmActionRequest
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty AcknowledgeAlarmActionRequest
acknowledgeActionRequests

instance Prelude.NFData BatchAcknowledgeAlarm where
  rnf :: BatchAcknowledgeAlarm -> ()
rnf BatchAcknowledgeAlarm' {NonEmpty AcknowledgeAlarmActionRequest
acknowledgeActionRequests :: NonEmpty AcknowledgeAlarmActionRequest
$sel:acknowledgeActionRequests:BatchAcknowledgeAlarm' :: BatchAcknowledgeAlarm -> NonEmpty AcknowledgeAlarmActionRequest
..} =
    forall a. NFData a => a -> ()
Prelude.rnf NonEmpty AcknowledgeAlarmActionRequest
acknowledgeActionRequests

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

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

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

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

-- | /See:/ 'newBatchAcknowledgeAlarmResponse' smart constructor.
data BatchAcknowledgeAlarmResponse = BatchAcknowledgeAlarmResponse'
  { -- | A list of errors associated with the request, or @null@ if there are no
    -- errors. Each error entry contains an entry ID that helps you identify
    -- the entry that failed.
    BatchAcknowledgeAlarmResponse -> Maybe [BatchAlarmActionErrorEntry]
errorEntries :: Prelude.Maybe [BatchAlarmActionErrorEntry],
    -- | The response's http status code.
    BatchAcknowledgeAlarmResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (BatchAcknowledgeAlarmResponse
-> BatchAcknowledgeAlarmResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchAcknowledgeAlarmResponse
-> BatchAcknowledgeAlarmResponse -> Bool
$c/= :: BatchAcknowledgeAlarmResponse
-> BatchAcknowledgeAlarmResponse -> Bool
== :: BatchAcknowledgeAlarmResponse
-> BatchAcknowledgeAlarmResponse -> Bool
$c== :: BatchAcknowledgeAlarmResponse
-> BatchAcknowledgeAlarmResponse -> Bool
Prelude.Eq, ReadPrec [BatchAcknowledgeAlarmResponse]
ReadPrec BatchAcknowledgeAlarmResponse
Int -> ReadS BatchAcknowledgeAlarmResponse
ReadS [BatchAcknowledgeAlarmResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchAcknowledgeAlarmResponse]
$creadListPrec :: ReadPrec [BatchAcknowledgeAlarmResponse]
readPrec :: ReadPrec BatchAcknowledgeAlarmResponse
$creadPrec :: ReadPrec BatchAcknowledgeAlarmResponse
readList :: ReadS [BatchAcknowledgeAlarmResponse]
$creadList :: ReadS [BatchAcknowledgeAlarmResponse]
readsPrec :: Int -> ReadS BatchAcknowledgeAlarmResponse
$creadsPrec :: Int -> ReadS BatchAcknowledgeAlarmResponse
Prelude.Read, Int -> BatchAcknowledgeAlarmResponse -> ShowS
[BatchAcknowledgeAlarmResponse] -> ShowS
BatchAcknowledgeAlarmResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchAcknowledgeAlarmResponse] -> ShowS
$cshowList :: [BatchAcknowledgeAlarmResponse] -> ShowS
show :: BatchAcknowledgeAlarmResponse -> String
$cshow :: BatchAcknowledgeAlarmResponse -> String
showsPrec :: Int -> BatchAcknowledgeAlarmResponse -> ShowS
$cshowsPrec :: Int -> BatchAcknowledgeAlarmResponse -> ShowS
Prelude.Show, forall x.
Rep BatchAcknowledgeAlarmResponse x
-> BatchAcknowledgeAlarmResponse
forall x.
BatchAcknowledgeAlarmResponse
-> Rep BatchAcknowledgeAlarmResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchAcknowledgeAlarmResponse x
-> BatchAcknowledgeAlarmResponse
$cfrom :: forall x.
BatchAcknowledgeAlarmResponse
-> Rep BatchAcknowledgeAlarmResponse x
Prelude.Generic)

-- |
-- Create a value of 'BatchAcknowledgeAlarmResponse' 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:
--
-- 'errorEntries', 'batchAcknowledgeAlarmResponse_errorEntries' - A list of errors associated with the request, or @null@ if there are no
-- errors. Each error entry contains an entry ID that helps you identify
-- the entry that failed.
--
-- 'httpStatus', 'batchAcknowledgeAlarmResponse_httpStatus' - The response's http status code.
newBatchAcknowledgeAlarmResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  BatchAcknowledgeAlarmResponse
newBatchAcknowledgeAlarmResponse :: Int -> BatchAcknowledgeAlarmResponse
newBatchAcknowledgeAlarmResponse Int
pHttpStatus_ =
  BatchAcknowledgeAlarmResponse'
    { $sel:errorEntries:BatchAcknowledgeAlarmResponse' :: Maybe [BatchAlarmActionErrorEntry]
errorEntries =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:BatchAcknowledgeAlarmResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of errors associated with the request, or @null@ if there are no
-- errors. Each error entry contains an entry ID that helps you identify
-- the entry that failed.
batchAcknowledgeAlarmResponse_errorEntries :: Lens.Lens' BatchAcknowledgeAlarmResponse (Prelude.Maybe [BatchAlarmActionErrorEntry])
batchAcknowledgeAlarmResponse_errorEntries :: Lens'
  BatchAcknowledgeAlarmResponse (Maybe [BatchAlarmActionErrorEntry])
batchAcknowledgeAlarmResponse_errorEntries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchAcknowledgeAlarmResponse' {Maybe [BatchAlarmActionErrorEntry]
errorEntries :: Maybe [BatchAlarmActionErrorEntry]
$sel:errorEntries:BatchAcknowledgeAlarmResponse' :: BatchAcknowledgeAlarmResponse -> Maybe [BatchAlarmActionErrorEntry]
errorEntries} -> Maybe [BatchAlarmActionErrorEntry]
errorEntries) (\s :: BatchAcknowledgeAlarmResponse
s@BatchAcknowledgeAlarmResponse' {} Maybe [BatchAlarmActionErrorEntry]
a -> BatchAcknowledgeAlarmResponse
s {$sel:errorEntries:BatchAcknowledgeAlarmResponse' :: Maybe [BatchAlarmActionErrorEntry]
errorEntries = Maybe [BatchAlarmActionErrorEntry]
a} :: BatchAcknowledgeAlarmResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.NFData BatchAcknowledgeAlarmResponse where
  rnf :: BatchAcknowledgeAlarmResponse -> ()
rnf BatchAcknowledgeAlarmResponse' {Int
Maybe [BatchAlarmActionErrorEntry]
httpStatus :: Int
errorEntries :: Maybe [BatchAlarmActionErrorEntry]
$sel:httpStatus:BatchAcknowledgeAlarmResponse' :: BatchAcknowledgeAlarmResponse -> Int
$sel:errorEntries:BatchAcknowledgeAlarmResponse' :: BatchAcknowledgeAlarmResponse -> Maybe [BatchAlarmActionErrorEntry]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [BatchAlarmActionErrorEntry]
errorEntries
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus