{-# LANGUAGE DisambiguateRecordFields #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.IoTEventsData.Types
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.IoTEventsData.Types
  ( -- * Service Configuration
    defaultService,

    -- * Errors
    _InternalFailureException,
    _InvalidRequestException,
    _ResourceNotFoundException,
    _ServiceUnavailableException,
    _ThrottlingException,

    -- * AlarmStateName
    AlarmStateName (..),

    -- * ComparisonOperator
    ComparisonOperator (..),

    -- * CustomerActionName
    CustomerActionName (..),

    -- * ErrorCode
    ErrorCode (..),

    -- * EventType
    EventType (..),

    -- * TriggerType
    TriggerType (..),

    -- * AcknowledgeActionConfiguration
    AcknowledgeActionConfiguration (..),
    newAcknowledgeActionConfiguration,
    acknowledgeActionConfiguration_note,

    -- * AcknowledgeAlarmActionRequest
    AcknowledgeAlarmActionRequest (..),
    newAcknowledgeAlarmActionRequest,
    acknowledgeAlarmActionRequest_keyValue,
    acknowledgeAlarmActionRequest_note,
    acknowledgeAlarmActionRequest_requestId,
    acknowledgeAlarmActionRequest_alarmModelName,

    -- * Alarm
    Alarm (..),
    newAlarm,
    alarm_alarmModelName,
    alarm_alarmModelVersion,
    alarm_alarmState,
    alarm_creationTime,
    alarm_keyValue,
    alarm_lastUpdateTime,
    alarm_severity,

    -- * AlarmState
    AlarmState (..),
    newAlarmState,
    alarmState_customerAction,
    alarmState_ruleEvaluation,
    alarmState_stateName,
    alarmState_systemEvent,

    -- * AlarmSummary
    AlarmSummary (..),
    newAlarmSummary,
    alarmSummary_alarmModelName,
    alarmSummary_alarmModelVersion,
    alarmSummary_creationTime,
    alarmSummary_keyValue,
    alarmSummary_lastUpdateTime,
    alarmSummary_stateName,

    -- * BatchAlarmActionErrorEntry
    BatchAlarmActionErrorEntry (..),
    newBatchAlarmActionErrorEntry,
    batchAlarmActionErrorEntry_errorCode,
    batchAlarmActionErrorEntry_errorMessage,
    batchAlarmActionErrorEntry_requestId,

    -- * BatchDeleteDetectorErrorEntry
    BatchDeleteDetectorErrorEntry (..),
    newBatchDeleteDetectorErrorEntry,
    batchDeleteDetectorErrorEntry_errorCode,
    batchDeleteDetectorErrorEntry_errorMessage,
    batchDeleteDetectorErrorEntry_messageId,

    -- * BatchPutMessageErrorEntry
    BatchPutMessageErrorEntry (..),
    newBatchPutMessageErrorEntry,
    batchPutMessageErrorEntry_errorCode,
    batchPutMessageErrorEntry_errorMessage,
    batchPutMessageErrorEntry_messageId,

    -- * BatchUpdateDetectorErrorEntry
    BatchUpdateDetectorErrorEntry (..),
    newBatchUpdateDetectorErrorEntry,
    batchUpdateDetectorErrorEntry_errorCode,
    batchUpdateDetectorErrorEntry_errorMessage,
    batchUpdateDetectorErrorEntry_messageId,

    -- * CustomerAction
    CustomerAction (..),
    newCustomerAction,
    customerAction_acknowledgeActionConfiguration,
    customerAction_actionName,
    customerAction_disableActionConfiguration,
    customerAction_enableActionConfiguration,
    customerAction_resetActionConfiguration,
    customerAction_snoozeActionConfiguration,

    -- * DeleteDetectorRequest
    DeleteDetectorRequest (..),
    newDeleteDetectorRequest,
    deleteDetectorRequest_keyValue,
    deleteDetectorRequest_messageId,
    deleteDetectorRequest_detectorModelName,

    -- * Detector
    Detector (..),
    newDetector,
    detector_creationTime,
    detector_detectorModelName,
    detector_detectorModelVersion,
    detector_keyValue,
    detector_lastUpdateTime,
    detector_state,

    -- * DetectorState
    DetectorState (..),
    newDetectorState,
    detectorState_stateName,
    detectorState_variables,
    detectorState_timers,

    -- * DetectorStateDefinition
    DetectorStateDefinition (..),
    newDetectorStateDefinition,
    detectorStateDefinition_stateName,
    detectorStateDefinition_variables,
    detectorStateDefinition_timers,

    -- * DetectorStateSummary
    DetectorStateSummary (..),
    newDetectorStateSummary,
    detectorStateSummary_stateName,

    -- * DetectorSummary
    DetectorSummary (..),
    newDetectorSummary,
    detectorSummary_creationTime,
    detectorSummary_detectorModelName,
    detectorSummary_detectorModelVersion,
    detectorSummary_keyValue,
    detectorSummary_lastUpdateTime,
    detectorSummary_state,

    -- * DisableActionConfiguration
    DisableActionConfiguration (..),
    newDisableActionConfiguration,
    disableActionConfiguration_note,

    -- * DisableAlarmActionRequest
    DisableAlarmActionRequest (..),
    newDisableAlarmActionRequest,
    disableAlarmActionRequest_keyValue,
    disableAlarmActionRequest_note,
    disableAlarmActionRequest_requestId,
    disableAlarmActionRequest_alarmModelName,

    -- * EnableActionConfiguration
    EnableActionConfiguration (..),
    newEnableActionConfiguration,
    enableActionConfiguration_note,

    -- * EnableAlarmActionRequest
    EnableAlarmActionRequest (..),
    newEnableAlarmActionRequest,
    enableAlarmActionRequest_keyValue,
    enableAlarmActionRequest_note,
    enableAlarmActionRequest_requestId,
    enableAlarmActionRequest_alarmModelName,

    -- * Message
    Message (..),
    newMessage,
    message_timestamp,
    message_messageId,
    message_inputName,
    message_payload,

    -- * ResetActionConfiguration
    ResetActionConfiguration (..),
    newResetActionConfiguration,
    resetActionConfiguration_note,

    -- * ResetAlarmActionRequest
    ResetAlarmActionRequest (..),
    newResetAlarmActionRequest,
    resetAlarmActionRequest_keyValue,
    resetAlarmActionRequest_note,
    resetAlarmActionRequest_requestId,
    resetAlarmActionRequest_alarmModelName,

    -- * RuleEvaluation
    RuleEvaluation (..),
    newRuleEvaluation,
    ruleEvaluation_simpleRuleEvaluation,

    -- * SimpleRuleEvaluation
    SimpleRuleEvaluation (..),
    newSimpleRuleEvaluation,
    simpleRuleEvaluation_inputPropertyValue,
    simpleRuleEvaluation_operator,
    simpleRuleEvaluation_thresholdValue,

    -- * SnoozeActionConfiguration
    SnoozeActionConfiguration (..),
    newSnoozeActionConfiguration,
    snoozeActionConfiguration_note,
    snoozeActionConfiguration_snoozeDuration,

    -- * SnoozeAlarmActionRequest
    SnoozeAlarmActionRequest (..),
    newSnoozeAlarmActionRequest,
    snoozeAlarmActionRequest_keyValue,
    snoozeAlarmActionRequest_note,
    snoozeAlarmActionRequest_requestId,
    snoozeAlarmActionRequest_alarmModelName,
    snoozeAlarmActionRequest_snoozeDuration,

    -- * StateChangeConfiguration
    StateChangeConfiguration (..),
    newStateChangeConfiguration,
    stateChangeConfiguration_triggerType,

    -- * SystemEvent
    SystemEvent (..),
    newSystemEvent,
    systemEvent_eventType,
    systemEvent_stateChangeConfiguration,

    -- * Timer
    Timer (..),
    newTimer,
    timer_name,
    timer_timestamp,

    -- * TimerDefinition
    TimerDefinition (..),
    newTimerDefinition,
    timerDefinition_name,
    timerDefinition_seconds,

    -- * TimestampValue
    TimestampValue (..),
    newTimestampValue,
    timestampValue_timeInMillis,

    -- * UpdateDetectorRequest
    UpdateDetectorRequest (..),
    newUpdateDetectorRequest,
    updateDetectorRequest_keyValue,
    updateDetectorRequest_messageId,
    updateDetectorRequest_detectorModelName,
    updateDetectorRequest_state,

    -- * Variable
    Variable (..),
    newVariable,
    variable_name,
    variable_value,

    -- * VariableDefinition
    VariableDefinition (..),
    newVariableDefinition,
    variableDefinition_name,
    variableDefinition_value,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import Amazonka.IoTEventsData.Types.AcknowledgeActionConfiguration
import Amazonka.IoTEventsData.Types.AcknowledgeAlarmActionRequest
import Amazonka.IoTEventsData.Types.Alarm
import Amazonka.IoTEventsData.Types.AlarmState
import Amazonka.IoTEventsData.Types.AlarmStateName
import Amazonka.IoTEventsData.Types.AlarmSummary
import Amazonka.IoTEventsData.Types.BatchAlarmActionErrorEntry
import Amazonka.IoTEventsData.Types.BatchDeleteDetectorErrorEntry
import Amazonka.IoTEventsData.Types.BatchPutMessageErrorEntry
import Amazonka.IoTEventsData.Types.BatchUpdateDetectorErrorEntry
import Amazonka.IoTEventsData.Types.ComparisonOperator
import Amazonka.IoTEventsData.Types.CustomerAction
import Amazonka.IoTEventsData.Types.CustomerActionName
import Amazonka.IoTEventsData.Types.DeleteDetectorRequest
import Amazonka.IoTEventsData.Types.Detector
import Amazonka.IoTEventsData.Types.DetectorState
import Amazonka.IoTEventsData.Types.DetectorStateDefinition
import Amazonka.IoTEventsData.Types.DetectorStateSummary
import Amazonka.IoTEventsData.Types.DetectorSummary
import Amazonka.IoTEventsData.Types.DisableActionConfiguration
import Amazonka.IoTEventsData.Types.DisableAlarmActionRequest
import Amazonka.IoTEventsData.Types.EnableActionConfiguration
import Amazonka.IoTEventsData.Types.EnableAlarmActionRequest
import Amazonka.IoTEventsData.Types.ErrorCode
import Amazonka.IoTEventsData.Types.EventType
import Amazonka.IoTEventsData.Types.Message
import Amazonka.IoTEventsData.Types.ResetActionConfiguration
import Amazonka.IoTEventsData.Types.ResetAlarmActionRequest
import Amazonka.IoTEventsData.Types.RuleEvaluation
import Amazonka.IoTEventsData.Types.SimpleRuleEvaluation
import Amazonka.IoTEventsData.Types.SnoozeActionConfiguration
import Amazonka.IoTEventsData.Types.SnoozeAlarmActionRequest
import Amazonka.IoTEventsData.Types.StateChangeConfiguration
import Amazonka.IoTEventsData.Types.SystemEvent
import Amazonka.IoTEventsData.Types.Timer
import Amazonka.IoTEventsData.Types.TimerDefinition
import Amazonka.IoTEventsData.Types.TimestampValue
import Amazonka.IoTEventsData.Types.TriggerType
import Amazonka.IoTEventsData.Types.UpdateDetectorRequest
import Amazonka.IoTEventsData.Types.Variable
import Amazonka.IoTEventsData.Types.VariableDefinition
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Sign.V4 as Sign

-- | API version @2018-10-23@ of the Amazon IoT Events Data SDK configuration.
defaultService :: Core.Service
defaultService :: Service
defaultService =
  Core.Service
    { $sel:abbrev:Service :: Abbrev
Core.abbrev = Abbrev
"IoTEventsData",
      $sel:signer:Service :: Signer
Core.signer = Signer
Sign.v4,
      $sel:endpointPrefix:Service :: ByteString
Core.endpointPrefix = ByteString
"data.iotevents",
      $sel:signingName:Service :: ByteString
Core.signingName = ByteString
"ioteventsdata",
      $sel:version:Service :: ByteString
Core.version = ByteString
"2018-10-23",
      $sel:s3AddressingStyle:Service :: S3AddressingStyle
Core.s3AddressingStyle = S3AddressingStyle
Core.S3AddressingStyleAuto,
      $sel:endpoint:Service :: Region -> Endpoint
Core.endpoint = Service -> Region -> Endpoint
Core.defaultEndpoint Service
defaultService,
      $sel:timeout:Service :: Maybe Seconds
Core.timeout = forall a. a -> Maybe a
Prelude.Just Seconds
70,
      $sel:check:Service :: Status -> Bool
Core.check = Status -> Bool
Core.statusSuccess,
      $sel:error:Service :: Status -> [Header] -> ByteStringLazy -> Error
Core.error = Abbrev -> Status -> [Header] -> ByteStringLazy -> Error
Core.parseJSONError Abbrev
"IoTEventsData",
      $sel:retry:Service :: Retry
Core.retry = Retry
retry
    }
  where
    retry :: Retry
retry =
      Core.Exponential
        { $sel:base:Exponential :: Double
Core.base = Double
5.0e-2,
          $sel:growth:Exponential :: Int
Core.growth = Int
2,
          $sel:attempts:Exponential :: Int
Core.attempts = Int
5,
          $sel:check:Exponential :: ServiceError -> Maybe Text
Core.check = forall {a}. IsString a => ServiceError -> Maybe a
check
        }
    check :: ServiceError -> Maybe a
check ServiceError
e
      | forall s a. Getting Any s a -> s -> Bool
Lens.has (forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
502) ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"bad_gateway"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has (forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
504) ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"gateway_timeout"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has (forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
500) ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"general_server_error"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has (forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
509) ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"limit_exceeded"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has
          ( forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
ErrorCode -> Optic' p f ServiceError ServiceError
Core.hasCode ErrorCode
"RequestThrottledException"
              forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400
          )
          ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"request_throttled_exception"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has (forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
503) ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"service_unavailable"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has
          ( forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
ErrorCode -> Optic' p f ServiceError ServiceError
Core.hasCode ErrorCode
"ThrottledException"
              forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400
          )
          ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"throttled_exception"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has
          ( forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
ErrorCode -> Optic' p f ServiceError ServiceError
Core.hasCode ErrorCode
"Throttling"
              forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400
          )
          ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"throttling"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has
          ( forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
ErrorCode -> Optic' p f ServiceError ServiceError
Core.hasCode ErrorCode
"ThrottlingException"
              forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400
          )
          ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"throttling_exception"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has
          ( forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
ErrorCode -> Optic' p f ServiceError ServiceError
Core.hasCode
              ErrorCode
"ProvisionedThroughputExceededException"
              forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400
          )
          ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"throughput_exceeded"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has (forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
429) ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"too_many_requests"
      | Bool
Prelude.otherwise = forall a. Maybe a
Prelude.Nothing

-- | An internal failure occurred.
_InternalFailureException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InternalFailureException :: forall a. AsError a => Fold a ServiceError
_InternalFailureException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InternalFailureException"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
500

-- | The request was invalid.
_InvalidRequestException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidRequestException :: forall a. AsError a => Fold a ServiceError
_InvalidRequestException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidRequestException"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400

-- | The resource was not found.
_ResourceNotFoundException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ResourceNotFoundException :: forall a. AsError a => Fold a ServiceError
_ResourceNotFoundException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ResourceNotFoundException"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
404

-- | The service is currently unavailable.
_ServiceUnavailableException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ServiceUnavailableException :: forall a. AsError a => Fold a ServiceError
_ServiceUnavailableException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ServiceUnavailableException"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
503

-- | The request could not be completed due to throttling.
_ThrottlingException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ThrottlingException :: forall a. AsError a => Fold a ServiceError
_ThrottlingException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ThrottlingException"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
429