module Stratosphere.GreengrassV2.Deployment.IoTJobAbortConfigProperty (
        module Exports, IoTJobAbortConfigProperty(..),
        mkIoTJobAbortConfigProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.GreengrassV2.Deployment.IoTJobAbortCriteriaProperty as Exports
import Stratosphere.ResourceProperties
data IoTJobAbortConfigProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-greengrassv2-deployment-iotjobabortconfig.html>
    IoTJobAbortConfigProperty {IoTJobAbortConfigProperty -> ()
haddock_workaround_ :: (),
                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-greengrassv2-deployment-iotjobabortconfig.html#cfn-greengrassv2-deployment-iotjobabortconfig-criterialist>
                               IoTJobAbortConfigProperty -> [IoTJobAbortCriteriaProperty]
criteriaList :: [IoTJobAbortCriteriaProperty]}
  deriving stock (IoTJobAbortConfigProperty -> IoTJobAbortConfigProperty -> Bool
(IoTJobAbortConfigProperty -> IoTJobAbortConfigProperty -> Bool)
-> (IoTJobAbortConfigProperty -> IoTJobAbortConfigProperty -> Bool)
-> Eq IoTJobAbortConfigProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IoTJobAbortConfigProperty -> IoTJobAbortConfigProperty -> Bool
== :: IoTJobAbortConfigProperty -> IoTJobAbortConfigProperty -> Bool
$c/= :: IoTJobAbortConfigProperty -> IoTJobAbortConfigProperty -> Bool
/= :: IoTJobAbortConfigProperty -> IoTJobAbortConfigProperty -> Bool
Prelude.Eq, Int -> IoTJobAbortConfigProperty -> ShowS
[IoTJobAbortConfigProperty] -> ShowS
IoTJobAbortConfigProperty -> String
(Int -> IoTJobAbortConfigProperty -> ShowS)
-> (IoTJobAbortConfigProperty -> String)
-> ([IoTJobAbortConfigProperty] -> ShowS)
-> Show IoTJobAbortConfigProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IoTJobAbortConfigProperty -> ShowS
showsPrec :: Int -> IoTJobAbortConfigProperty -> ShowS
$cshow :: IoTJobAbortConfigProperty -> String
show :: IoTJobAbortConfigProperty -> String
$cshowList :: [IoTJobAbortConfigProperty] -> ShowS
showList :: [IoTJobAbortConfigProperty] -> ShowS
Prelude.Show)
mkIoTJobAbortConfigProperty ::
  [IoTJobAbortCriteriaProperty] -> IoTJobAbortConfigProperty
mkIoTJobAbortConfigProperty :: [IoTJobAbortCriteriaProperty] -> IoTJobAbortConfigProperty
mkIoTJobAbortConfigProperty [IoTJobAbortCriteriaProperty]
criteriaList
  = IoTJobAbortConfigProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), criteriaList :: [IoTJobAbortCriteriaProperty]
criteriaList = [IoTJobAbortCriteriaProperty]
criteriaList}
instance ToResourceProperties IoTJobAbortConfigProperty where
  toResourceProperties :: IoTJobAbortConfigProperty -> ResourceProperties
toResourceProperties IoTJobAbortConfigProperty {[IoTJobAbortCriteriaProperty]
()
haddock_workaround_ :: IoTJobAbortConfigProperty -> ()
criteriaList :: IoTJobAbortConfigProperty -> [IoTJobAbortCriteriaProperty]
haddock_workaround_ :: ()
criteriaList :: [IoTJobAbortCriteriaProperty]
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::GreengrassV2::Deployment.IoTJobAbortConfig",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"CriteriaList" Key -> [IoTJobAbortCriteriaProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [IoTJobAbortCriteriaProperty]
criteriaList]}
instance JSON.ToJSON IoTJobAbortConfigProperty where
  toJSON :: IoTJobAbortConfigProperty -> Value
toJSON IoTJobAbortConfigProperty {[IoTJobAbortCriteriaProperty]
()
haddock_workaround_ :: IoTJobAbortConfigProperty -> ()
criteriaList :: IoTJobAbortConfigProperty -> [IoTJobAbortCriteriaProperty]
haddock_workaround_ :: ()
criteriaList :: [IoTJobAbortCriteriaProperty]
..}
    = [(Key, Value)] -> Value
JSON.object [Key
"CriteriaList" Key -> [IoTJobAbortCriteriaProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [IoTJobAbortCriteriaProperty]
criteriaList]
instance Property "CriteriaList" IoTJobAbortConfigProperty where
  type PropertyType "CriteriaList" IoTJobAbortConfigProperty = [IoTJobAbortCriteriaProperty]
  set :: PropertyType "CriteriaList" IoTJobAbortConfigProperty
-> IoTJobAbortConfigProperty -> IoTJobAbortConfigProperty
set PropertyType "CriteriaList" IoTJobAbortConfigProperty
newValue IoTJobAbortConfigProperty {[IoTJobAbortCriteriaProperty]
()
haddock_workaround_ :: IoTJobAbortConfigProperty -> ()
criteriaList :: IoTJobAbortConfigProperty -> [IoTJobAbortCriteriaProperty]
haddock_workaround_ :: ()
criteriaList :: [IoTJobAbortCriteriaProperty]
..}
    = IoTJobAbortConfigProperty {criteriaList :: [IoTJobAbortCriteriaProperty]
criteriaList = [IoTJobAbortCriteriaProperty]
PropertyType "CriteriaList" IoTJobAbortConfigProperty
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}