{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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.Types.DetectorStateDefinition
-- 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.DetectorStateDefinition 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.TimerDefinition
import Amazonka.IoTEventsData.Types.VariableDefinition
import qualified Amazonka.Prelude as Prelude

-- | The new state, variable values, and timer settings of the detector
-- (instance).
--
-- /See:/ 'newDetectorStateDefinition' smart constructor.
data DetectorStateDefinition = DetectorStateDefinition'
  { -- | The name of the new state of the detector (instance).
    DetectorStateDefinition -> Text
stateName :: Prelude.Text,
    -- | The new values of the detector\'s variables. Any variable whose value
    -- isn\'t specified is cleared.
    DetectorStateDefinition -> [VariableDefinition]
variables :: [VariableDefinition],
    -- | The new values of the detector\'s timers. Any timer whose value isn\'t
    -- specified is cleared, and its timeout event won\'t occur.
    DetectorStateDefinition -> [TimerDefinition]
timers :: [TimerDefinition]
  }
  deriving (DetectorStateDefinition -> DetectorStateDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DetectorStateDefinition -> DetectorStateDefinition -> Bool
$c/= :: DetectorStateDefinition -> DetectorStateDefinition -> Bool
== :: DetectorStateDefinition -> DetectorStateDefinition -> Bool
$c== :: DetectorStateDefinition -> DetectorStateDefinition -> Bool
Prelude.Eq, ReadPrec [DetectorStateDefinition]
ReadPrec DetectorStateDefinition
Int -> ReadS DetectorStateDefinition
ReadS [DetectorStateDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DetectorStateDefinition]
$creadListPrec :: ReadPrec [DetectorStateDefinition]
readPrec :: ReadPrec DetectorStateDefinition
$creadPrec :: ReadPrec DetectorStateDefinition
readList :: ReadS [DetectorStateDefinition]
$creadList :: ReadS [DetectorStateDefinition]
readsPrec :: Int -> ReadS DetectorStateDefinition
$creadsPrec :: Int -> ReadS DetectorStateDefinition
Prelude.Read, Int -> DetectorStateDefinition -> ShowS
[DetectorStateDefinition] -> ShowS
DetectorStateDefinition -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DetectorStateDefinition] -> ShowS
$cshowList :: [DetectorStateDefinition] -> ShowS
show :: DetectorStateDefinition -> String
$cshow :: DetectorStateDefinition -> String
showsPrec :: Int -> DetectorStateDefinition -> ShowS
$cshowsPrec :: Int -> DetectorStateDefinition -> ShowS
Prelude.Show, forall x. Rep DetectorStateDefinition x -> DetectorStateDefinition
forall x. DetectorStateDefinition -> Rep DetectorStateDefinition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DetectorStateDefinition x -> DetectorStateDefinition
$cfrom :: forall x. DetectorStateDefinition -> Rep DetectorStateDefinition x
Prelude.Generic)

-- |
-- Create a value of 'DetectorStateDefinition' 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:
--
-- 'stateName', 'detectorStateDefinition_stateName' - The name of the new state of the detector (instance).
--
-- 'variables', 'detectorStateDefinition_variables' - The new values of the detector\'s variables. Any variable whose value
-- isn\'t specified is cleared.
--
-- 'timers', 'detectorStateDefinition_timers' - The new values of the detector\'s timers. Any timer whose value isn\'t
-- specified is cleared, and its timeout event won\'t occur.
newDetectorStateDefinition ::
  -- | 'stateName'
  Prelude.Text ->
  DetectorStateDefinition
newDetectorStateDefinition :: Text -> DetectorStateDefinition
newDetectorStateDefinition Text
pStateName_ =
  DetectorStateDefinition'
    { $sel:stateName:DetectorStateDefinition' :: Text
stateName = Text
pStateName_,
      $sel:variables:DetectorStateDefinition' :: [VariableDefinition]
variables = forall a. Monoid a => a
Prelude.mempty,
      $sel:timers:DetectorStateDefinition' :: [TimerDefinition]
timers = forall a. Monoid a => a
Prelude.mempty
    }

-- | The name of the new state of the detector (instance).
detectorStateDefinition_stateName :: Lens.Lens' DetectorStateDefinition Prelude.Text
detectorStateDefinition_stateName :: Lens' DetectorStateDefinition Text
detectorStateDefinition_stateName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetectorStateDefinition' {Text
stateName :: Text
$sel:stateName:DetectorStateDefinition' :: DetectorStateDefinition -> Text
stateName} -> Text
stateName) (\s :: DetectorStateDefinition
s@DetectorStateDefinition' {} Text
a -> DetectorStateDefinition
s {$sel:stateName:DetectorStateDefinition' :: Text
stateName = Text
a} :: DetectorStateDefinition)

-- | The new values of the detector\'s variables. Any variable whose value
-- isn\'t specified is cleared.
detectorStateDefinition_variables :: Lens.Lens' DetectorStateDefinition [VariableDefinition]
detectorStateDefinition_variables :: Lens' DetectorStateDefinition [VariableDefinition]
detectorStateDefinition_variables = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetectorStateDefinition' {[VariableDefinition]
variables :: [VariableDefinition]
$sel:variables:DetectorStateDefinition' :: DetectorStateDefinition -> [VariableDefinition]
variables} -> [VariableDefinition]
variables) (\s :: DetectorStateDefinition
s@DetectorStateDefinition' {} [VariableDefinition]
a -> DetectorStateDefinition
s {$sel:variables:DetectorStateDefinition' :: [VariableDefinition]
variables = [VariableDefinition]
a} :: DetectorStateDefinition) 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

-- | The new values of the detector\'s timers. Any timer whose value isn\'t
-- specified is cleared, and its timeout event won\'t occur.
detectorStateDefinition_timers :: Lens.Lens' DetectorStateDefinition [TimerDefinition]
detectorStateDefinition_timers :: Lens' DetectorStateDefinition [TimerDefinition]
detectorStateDefinition_timers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetectorStateDefinition' {[TimerDefinition]
timers :: [TimerDefinition]
$sel:timers:DetectorStateDefinition' :: DetectorStateDefinition -> [TimerDefinition]
timers} -> [TimerDefinition]
timers) (\s :: DetectorStateDefinition
s@DetectorStateDefinition' {} [TimerDefinition]
a -> DetectorStateDefinition
s {$sel:timers:DetectorStateDefinition' :: [TimerDefinition]
timers = [TimerDefinition]
a} :: DetectorStateDefinition) 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 Prelude.Hashable DetectorStateDefinition where
  hashWithSalt :: Int -> DetectorStateDefinition -> Int
hashWithSalt Int
_salt DetectorStateDefinition' {[TimerDefinition]
[VariableDefinition]
Text
timers :: [TimerDefinition]
variables :: [VariableDefinition]
stateName :: Text
$sel:timers:DetectorStateDefinition' :: DetectorStateDefinition -> [TimerDefinition]
$sel:variables:DetectorStateDefinition' :: DetectorStateDefinition -> [VariableDefinition]
$sel:stateName:DetectorStateDefinition' :: DetectorStateDefinition -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
stateName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [VariableDefinition]
variables
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [TimerDefinition]
timers

instance Prelude.NFData DetectorStateDefinition where
  rnf :: DetectorStateDefinition -> ()
rnf DetectorStateDefinition' {[TimerDefinition]
[VariableDefinition]
Text
timers :: [TimerDefinition]
variables :: [VariableDefinition]
stateName :: Text
$sel:timers:DetectorStateDefinition' :: DetectorStateDefinition -> [TimerDefinition]
$sel:variables:DetectorStateDefinition' :: DetectorStateDefinition -> [VariableDefinition]
$sel:stateName:DetectorStateDefinition' :: DetectorStateDefinition -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
stateName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [VariableDefinition]
variables
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [TimerDefinition]
timers

instance Data.ToJSON DetectorStateDefinition where
  toJSON :: DetectorStateDefinition -> Value
toJSON DetectorStateDefinition' {[TimerDefinition]
[VariableDefinition]
Text
timers :: [TimerDefinition]
variables :: [VariableDefinition]
stateName :: Text
$sel:timers:DetectorStateDefinition' :: DetectorStateDefinition -> [TimerDefinition]
$sel:variables:DetectorStateDefinition' :: DetectorStateDefinition -> [VariableDefinition]
$sel:stateName:DetectorStateDefinition' :: DetectorStateDefinition -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"stateName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
stateName),
            forall a. a -> Maybe a
Prelude.Just (Key
"variables" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [VariableDefinition]
variables),
            forall a. a -> Maybe a
Prelude.Just (Key
"timers" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [TimerDefinition]
timers)
          ]
      )