module Stratosphere.FIS.ExperimentTemplate.CloudWatchLogsConfigurationProperty (
        CloudWatchLogsConfigurationProperty(..),
        mkCloudWatchLogsConfigurationProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data CloudWatchLogsConfigurationProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-fis-experimenttemplate-cloudwatchlogsconfiguration.html>
    CloudWatchLogsConfigurationProperty {CloudWatchLogsConfigurationProperty -> ()
haddock_workaround_ :: (),
                                         -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-fis-experimenttemplate-cloudwatchlogsconfiguration.html#cfn-fis-experimenttemplate-cloudwatchlogsconfiguration-loggrouparn>
                                         CloudWatchLogsConfigurationProperty -> Value Text
logGroupArn :: (Value Prelude.Text)}
  deriving stock (CloudWatchLogsConfigurationProperty
-> CloudWatchLogsConfigurationProperty -> Bool
(CloudWatchLogsConfigurationProperty
 -> CloudWatchLogsConfigurationProperty -> Bool)
-> (CloudWatchLogsConfigurationProperty
    -> CloudWatchLogsConfigurationProperty -> Bool)
-> Eq CloudWatchLogsConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CloudWatchLogsConfigurationProperty
-> CloudWatchLogsConfigurationProperty -> Bool
== :: CloudWatchLogsConfigurationProperty
-> CloudWatchLogsConfigurationProperty -> Bool
$c/= :: CloudWatchLogsConfigurationProperty
-> CloudWatchLogsConfigurationProperty -> Bool
/= :: CloudWatchLogsConfigurationProperty
-> CloudWatchLogsConfigurationProperty -> Bool
Prelude.Eq, Int -> CloudWatchLogsConfigurationProperty -> ShowS
[CloudWatchLogsConfigurationProperty] -> ShowS
CloudWatchLogsConfigurationProperty -> String
(Int -> CloudWatchLogsConfigurationProperty -> ShowS)
-> (CloudWatchLogsConfigurationProperty -> String)
-> ([CloudWatchLogsConfigurationProperty] -> ShowS)
-> Show CloudWatchLogsConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CloudWatchLogsConfigurationProperty -> ShowS
showsPrec :: Int -> CloudWatchLogsConfigurationProperty -> ShowS
$cshow :: CloudWatchLogsConfigurationProperty -> String
show :: CloudWatchLogsConfigurationProperty -> String
$cshowList :: [CloudWatchLogsConfigurationProperty] -> ShowS
showList :: [CloudWatchLogsConfigurationProperty] -> ShowS
Prelude.Show)
mkCloudWatchLogsConfigurationProperty ::
  Value Prelude.Text -> CloudWatchLogsConfigurationProperty
mkCloudWatchLogsConfigurationProperty :: Value Text -> CloudWatchLogsConfigurationProperty
mkCloudWatchLogsConfigurationProperty Value Text
logGroupArn
  = CloudWatchLogsConfigurationProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), logGroupArn :: Value Text
logGroupArn = Value Text
logGroupArn}
instance ToResourceProperties CloudWatchLogsConfigurationProperty where
  toResourceProperties :: CloudWatchLogsConfigurationProperty -> ResourceProperties
toResourceProperties CloudWatchLogsConfigurationProperty {()
Value Text
haddock_workaround_ :: CloudWatchLogsConfigurationProperty -> ()
logGroupArn :: CloudWatchLogsConfigurationProperty -> Value Text
haddock_workaround_ :: ()
logGroupArn :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::FIS::ExperimentTemplate.CloudWatchLogsConfiguration",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"LogGroupArn" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
logGroupArn]}
instance JSON.ToJSON CloudWatchLogsConfigurationProperty where
  toJSON :: CloudWatchLogsConfigurationProperty -> Value
toJSON CloudWatchLogsConfigurationProperty {()
Value Text
haddock_workaround_ :: CloudWatchLogsConfigurationProperty -> ()
logGroupArn :: CloudWatchLogsConfigurationProperty -> Value Text
haddock_workaround_ :: ()
logGroupArn :: Value Text
..}
    = [(Key, Value)] -> Value
JSON.object [Key
"LogGroupArn" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
logGroupArn]
instance Property "LogGroupArn" CloudWatchLogsConfigurationProperty where
  type PropertyType "LogGroupArn" CloudWatchLogsConfigurationProperty = Value Prelude.Text
  set :: PropertyType "LogGroupArn" CloudWatchLogsConfigurationProperty
-> CloudWatchLogsConfigurationProperty
-> CloudWatchLogsConfigurationProperty
set PropertyType "LogGroupArn" CloudWatchLogsConfigurationProperty
newValue CloudWatchLogsConfigurationProperty {()
Value Text
haddock_workaround_ :: CloudWatchLogsConfigurationProperty -> ()
logGroupArn :: CloudWatchLogsConfigurationProperty -> Value Text
haddock_workaround_ :: ()
logGroupArn :: Value Text
..}
    = CloudWatchLogsConfigurationProperty {logGroupArn :: Value Text
logGroupArn = PropertyType "LogGroupArn" CloudWatchLogsConfigurationProperty
Value Text
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}