module Stratosphere.MSK.Cluster.BrokerLogsProperty (
module Exports, BrokerLogsProperty(..), mkBrokerLogsProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.MSK.Cluster.CloudWatchLogsProperty as Exports
import {-# SOURCE #-} Stratosphere.MSK.Cluster.FirehoseProperty as Exports
import {-# SOURCE #-} Stratosphere.MSK.Cluster.S3Property as Exports
import Stratosphere.ResourceProperties
data BrokerLogsProperty
=
BrokerLogsProperty {BrokerLogsProperty -> ()
haddock_workaround_ :: (),
BrokerLogsProperty -> Maybe CloudWatchLogsProperty
cloudWatchLogs :: (Prelude.Maybe CloudWatchLogsProperty),
BrokerLogsProperty -> Maybe FirehoseProperty
firehose :: (Prelude.Maybe FirehoseProperty),
BrokerLogsProperty -> Maybe S3Property
s3 :: (Prelude.Maybe S3Property)}
deriving stock (BrokerLogsProperty -> BrokerLogsProperty -> Bool
(BrokerLogsProperty -> BrokerLogsProperty -> Bool)
-> (BrokerLogsProperty -> BrokerLogsProperty -> Bool)
-> Eq BrokerLogsProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BrokerLogsProperty -> BrokerLogsProperty -> Bool
== :: BrokerLogsProperty -> BrokerLogsProperty -> Bool
$c/= :: BrokerLogsProperty -> BrokerLogsProperty -> Bool
/= :: BrokerLogsProperty -> BrokerLogsProperty -> Bool
Prelude.Eq, Int -> BrokerLogsProperty -> ShowS
[BrokerLogsProperty] -> ShowS
BrokerLogsProperty -> String
(Int -> BrokerLogsProperty -> ShowS)
-> (BrokerLogsProperty -> String)
-> ([BrokerLogsProperty] -> ShowS)
-> Show BrokerLogsProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BrokerLogsProperty -> ShowS
showsPrec :: Int -> BrokerLogsProperty -> ShowS
$cshow :: BrokerLogsProperty -> String
show :: BrokerLogsProperty -> String
$cshowList :: [BrokerLogsProperty] -> ShowS
showList :: [BrokerLogsProperty] -> ShowS
Prelude.Show)
mkBrokerLogsProperty :: BrokerLogsProperty
mkBrokerLogsProperty :: BrokerLogsProperty
mkBrokerLogsProperty
= BrokerLogsProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), cloudWatchLogs :: Maybe CloudWatchLogsProperty
cloudWatchLogs = Maybe CloudWatchLogsProperty
forall a. Maybe a
Prelude.Nothing,
firehose :: Maybe FirehoseProperty
firehose = Maybe FirehoseProperty
forall a. Maybe a
Prelude.Nothing, s3 :: Maybe S3Property
s3 = Maybe S3Property
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties BrokerLogsProperty where
toResourceProperties :: BrokerLogsProperty -> ResourceProperties
toResourceProperties BrokerLogsProperty {Maybe CloudWatchLogsProperty
Maybe FirehoseProperty
Maybe S3Property
()
haddock_workaround_ :: BrokerLogsProperty -> ()
cloudWatchLogs :: BrokerLogsProperty -> Maybe CloudWatchLogsProperty
firehose :: BrokerLogsProperty -> Maybe FirehoseProperty
s3 :: BrokerLogsProperty -> Maybe S3Property
haddock_workaround_ :: ()
cloudWatchLogs :: Maybe CloudWatchLogsProperty
firehose :: Maybe FirehoseProperty
s3 :: Maybe S3Property
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::MSK::Cluster.BrokerLogs",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> CloudWatchLogsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CloudWatchLogs" (CloudWatchLogsProperty -> (Key, Value))
-> Maybe CloudWatchLogsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CloudWatchLogsProperty
cloudWatchLogs,
Key -> FirehoseProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Firehose" (FirehoseProperty -> (Key, Value))
-> Maybe FirehoseProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe FirehoseProperty
firehose,
Key -> S3Property -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"S3" (S3Property -> (Key, Value))
-> Maybe S3Property -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe S3Property
s3])}
instance JSON.ToJSON BrokerLogsProperty where
toJSON :: BrokerLogsProperty -> Value
toJSON BrokerLogsProperty {Maybe CloudWatchLogsProperty
Maybe FirehoseProperty
Maybe S3Property
()
haddock_workaround_ :: BrokerLogsProperty -> ()
cloudWatchLogs :: BrokerLogsProperty -> Maybe CloudWatchLogsProperty
firehose :: BrokerLogsProperty -> Maybe FirehoseProperty
s3 :: BrokerLogsProperty -> Maybe S3Property
haddock_workaround_ :: ()
cloudWatchLogs :: Maybe CloudWatchLogsProperty
firehose :: Maybe FirehoseProperty
s3 :: Maybe S3Property
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> CloudWatchLogsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CloudWatchLogs" (CloudWatchLogsProperty -> (Key, Value))
-> Maybe CloudWatchLogsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CloudWatchLogsProperty
cloudWatchLogs,
Key -> FirehoseProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Firehose" (FirehoseProperty -> (Key, Value))
-> Maybe FirehoseProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe FirehoseProperty
firehose,
Key -> S3Property -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"S3" (S3Property -> (Key, Value))
-> Maybe S3Property -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe S3Property
s3]))
instance Property "CloudWatchLogs" BrokerLogsProperty where
type PropertyType "CloudWatchLogs" BrokerLogsProperty = CloudWatchLogsProperty
set :: PropertyType "CloudWatchLogs" BrokerLogsProperty
-> BrokerLogsProperty -> BrokerLogsProperty
set PropertyType "CloudWatchLogs" BrokerLogsProperty
newValue BrokerLogsProperty {Maybe CloudWatchLogsProperty
Maybe FirehoseProperty
Maybe S3Property
()
haddock_workaround_ :: BrokerLogsProperty -> ()
cloudWatchLogs :: BrokerLogsProperty -> Maybe CloudWatchLogsProperty
firehose :: BrokerLogsProperty -> Maybe FirehoseProperty
s3 :: BrokerLogsProperty -> Maybe S3Property
haddock_workaround_ :: ()
cloudWatchLogs :: Maybe CloudWatchLogsProperty
firehose :: Maybe FirehoseProperty
s3 :: Maybe S3Property
..}
= BrokerLogsProperty {cloudWatchLogs :: Maybe CloudWatchLogsProperty
cloudWatchLogs = CloudWatchLogsProperty -> Maybe CloudWatchLogsProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "CloudWatchLogs" BrokerLogsProperty
CloudWatchLogsProperty
newValue, Maybe FirehoseProperty
Maybe S3Property
()
haddock_workaround_ :: ()
firehose :: Maybe FirehoseProperty
s3 :: Maybe S3Property
haddock_workaround_ :: ()
firehose :: Maybe FirehoseProperty
s3 :: Maybe S3Property
..}
instance Property "Firehose" BrokerLogsProperty where
type PropertyType "Firehose" BrokerLogsProperty = FirehoseProperty
set :: PropertyType "Firehose" BrokerLogsProperty
-> BrokerLogsProperty -> BrokerLogsProperty
set PropertyType "Firehose" BrokerLogsProperty
newValue BrokerLogsProperty {Maybe CloudWatchLogsProperty
Maybe FirehoseProperty
Maybe S3Property
()
haddock_workaround_ :: BrokerLogsProperty -> ()
cloudWatchLogs :: BrokerLogsProperty -> Maybe CloudWatchLogsProperty
firehose :: BrokerLogsProperty -> Maybe FirehoseProperty
s3 :: BrokerLogsProperty -> Maybe S3Property
haddock_workaround_ :: ()
cloudWatchLogs :: Maybe CloudWatchLogsProperty
firehose :: Maybe FirehoseProperty
s3 :: Maybe S3Property
..}
= BrokerLogsProperty {firehose :: Maybe FirehoseProperty
firehose = FirehoseProperty -> Maybe FirehoseProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Firehose" BrokerLogsProperty
FirehoseProperty
newValue, Maybe CloudWatchLogsProperty
Maybe S3Property
()
haddock_workaround_ :: ()
cloudWatchLogs :: Maybe CloudWatchLogsProperty
s3 :: Maybe S3Property
haddock_workaround_ :: ()
cloudWatchLogs :: Maybe CloudWatchLogsProperty
s3 :: Maybe S3Property
..}
instance Property "S3" BrokerLogsProperty where
type PropertyType "S3" BrokerLogsProperty = S3Property
set :: PropertyType "S3" BrokerLogsProperty
-> BrokerLogsProperty -> BrokerLogsProperty
set PropertyType "S3" BrokerLogsProperty
newValue BrokerLogsProperty {Maybe CloudWatchLogsProperty
Maybe FirehoseProperty
Maybe S3Property
()
haddock_workaround_ :: BrokerLogsProperty -> ()
cloudWatchLogs :: BrokerLogsProperty -> Maybe CloudWatchLogsProperty
firehose :: BrokerLogsProperty -> Maybe FirehoseProperty
s3 :: BrokerLogsProperty -> Maybe S3Property
haddock_workaround_ :: ()
cloudWatchLogs :: Maybe CloudWatchLogsProperty
firehose :: Maybe FirehoseProperty
s3 :: Maybe S3Property
..}
= BrokerLogsProperty {s3 :: Maybe S3Property
s3 = S3Property -> Maybe S3Property
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "S3" BrokerLogsProperty
S3Property
newValue, Maybe CloudWatchLogsProperty
Maybe FirehoseProperty
()
haddock_workaround_ :: ()
cloudWatchLogs :: Maybe CloudWatchLogsProperty
firehose :: Maybe FirehoseProperty
haddock_workaround_ :: ()
cloudWatchLogs :: Maybe CloudWatchLogsProperty
firehose :: Maybe FirehoseProperty
..}