module Stratosphere.Timestream.InfluxDBInstance.LogDeliveryConfigurationProperty (
        module Exports, LogDeliveryConfigurationProperty(..),
        mkLogDeliveryConfigurationProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Timestream.InfluxDBInstance.S3ConfigurationProperty as Exports
import Stratosphere.ResourceProperties
data LogDeliveryConfigurationProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-timestream-influxdbinstance-logdeliveryconfiguration.html>
    LogDeliveryConfigurationProperty {LogDeliveryConfigurationProperty -> ()
haddock_workaround_ :: (),
                                      -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-timestream-influxdbinstance-logdeliveryconfiguration.html#cfn-timestream-influxdbinstance-logdeliveryconfiguration-s3configuration>
                                      LogDeliveryConfigurationProperty -> S3ConfigurationProperty
s3Configuration :: S3ConfigurationProperty}
  deriving stock (LogDeliveryConfigurationProperty
-> LogDeliveryConfigurationProperty -> Bool
(LogDeliveryConfigurationProperty
 -> LogDeliveryConfigurationProperty -> Bool)
-> (LogDeliveryConfigurationProperty
    -> LogDeliveryConfigurationProperty -> Bool)
-> Eq LogDeliveryConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LogDeliveryConfigurationProperty
-> LogDeliveryConfigurationProperty -> Bool
== :: LogDeliveryConfigurationProperty
-> LogDeliveryConfigurationProperty -> Bool
$c/= :: LogDeliveryConfigurationProperty
-> LogDeliveryConfigurationProperty -> Bool
/= :: LogDeliveryConfigurationProperty
-> LogDeliveryConfigurationProperty -> Bool
Prelude.Eq, Int -> LogDeliveryConfigurationProperty -> ShowS
[LogDeliveryConfigurationProperty] -> ShowS
LogDeliveryConfigurationProperty -> String
(Int -> LogDeliveryConfigurationProperty -> ShowS)
-> (LogDeliveryConfigurationProperty -> String)
-> ([LogDeliveryConfigurationProperty] -> ShowS)
-> Show LogDeliveryConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LogDeliveryConfigurationProperty -> ShowS
showsPrec :: Int -> LogDeliveryConfigurationProperty -> ShowS
$cshow :: LogDeliveryConfigurationProperty -> String
show :: LogDeliveryConfigurationProperty -> String
$cshowList :: [LogDeliveryConfigurationProperty] -> ShowS
showList :: [LogDeliveryConfigurationProperty] -> ShowS
Prelude.Show)
mkLogDeliveryConfigurationProperty ::
  S3ConfigurationProperty -> LogDeliveryConfigurationProperty
mkLogDeliveryConfigurationProperty :: S3ConfigurationProperty -> LogDeliveryConfigurationProperty
mkLogDeliveryConfigurationProperty S3ConfigurationProperty
s3Configuration
  = LogDeliveryConfigurationProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), s3Configuration :: S3ConfigurationProperty
s3Configuration = S3ConfigurationProperty
s3Configuration}
instance ToResourceProperties LogDeliveryConfigurationProperty where
  toResourceProperties :: LogDeliveryConfigurationProperty -> ResourceProperties
toResourceProperties LogDeliveryConfigurationProperty {()
S3ConfigurationProperty
haddock_workaround_ :: LogDeliveryConfigurationProperty -> ()
s3Configuration :: LogDeliveryConfigurationProperty -> S3ConfigurationProperty
haddock_workaround_ :: ()
s3Configuration :: S3ConfigurationProperty
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::Timestream::InfluxDBInstance.LogDeliveryConfiguration",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"S3Configuration" Key -> S3ConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= S3ConfigurationProperty
s3Configuration]}
instance JSON.ToJSON LogDeliveryConfigurationProperty where
  toJSON :: LogDeliveryConfigurationProperty -> Value
toJSON LogDeliveryConfigurationProperty {()
S3ConfigurationProperty
haddock_workaround_ :: LogDeliveryConfigurationProperty -> ()
s3Configuration :: LogDeliveryConfigurationProperty -> S3ConfigurationProperty
haddock_workaround_ :: ()
s3Configuration :: S3ConfigurationProperty
..}
    = [(Key, Value)] -> Value
JSON.object [Key
"S3Configuration" Key -> S3ConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= S3ConfigurationProperty
s3Configuration]
instance Property "S3Configuration" LogDeliveryConfigurationProperty where
  type PropertyType "S3Configuration" LogDeliveryConfigurationProperty = S3ConfigurationProperty
  set :: PropertyType "S3Configuration" LogDeliveryConfigurationProperty
-> LogDeliveryConfigurationProperty
-> LogDeliveryConfigurationProperty
set PropertyType "S3Configuration" LogDeliveryConfigurationProperty
newValue LogDeliveryConfigurationProperty {()
S3ConfigurationProperty
haddock_workaround_ :: LogDeliveryConfigurationProperty -> ()
s3Configuration :: LogDeliveryConfigurationProperty -> S3ConfigurationProperty
haddock_workaround_ :: ()
s3Configuration :: S3ConfigurationProperty
..}
    = LogDeliveryConfigurationProperty {s3Configuration :: S3ConfigurationProperty
s3Configuration = PropertyType "S3Configuration" LogDeliveryConfigurationProperty
S3ConfigurationProperty
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}