module Stratosphere.MSK.Cluster.VpcConnectivityProperty (
module Exports, VpcConnectivityProperty(..),
mkVpcConnectivityProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.MSK.Cluster.VpcConnectivityClientAuthenticationProperty as Exports
import Stratosphere.ResourceProperties
data VpcConnectivityProperty
=
VpcConnectivityProperty {VpcConnectivityProperty -> ()
haddock_workaround_ :: (),
VpcConnectivityProperty
-> Maybe VpcConnectivityClientAuthenticationProperty
clientAuthentication :: (Prelude.Maybe VpcConnectivityClientAuthenticationProperty)}
deriving stock (VpcConnectivityProperty -> VpcConnectivityProperty -> Bool
(VpcConnectivityProperty -> VpcConnectivityProperty -> Bool)
-> (VpcConnectivityProperty -> VpcConnectivityProperty -> Bool)
-> Eq VpcConnectivityProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VpcConnectivityProperty -> VpcConnectivityProperty -> Bool
== :: VpcConnectivityProperty -> VpcConnectivityProperty -> Bool
$c/= :: VpcConnectivityProperty -> VpcConnectivityProperty -> Bool
/= :: VpcConnectivityProperty -> VpcConnectivityProperty -> Bool
Prelude.Eq, Int -> VpcConnectivityProperty -> ShowS
[VpcConnectivityProperty] -> ShowS
VpcConnectivityProperty -> String
(Int -> VpcConnectivityProperty -> ShowS)
-> (VpcConnectivityProperty -> String)
-> ([VpcConnectivityProperty] -> ShowS)
-> Show VpcConnectivityProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VpcConnectivityProperty -> ShowS
showsPrec :: Int -> VpcConnectivityProperty -> ShowS
$cshow :: VpcConnectivityProperty -> String
show :: VpcConnectivityProperty -> String
$cshowList :: [VpcConnectivityProperty] -> ShowS
showList :: [VpcConnectivityProperty] -> ShowS
Prelude.Show)
mkVpcConnectivityProperty :: VpcConnectivityProperty
mkVpcConnectivityProperty :: VpcConnectivityProperty
mkVpcConnectivityProperty
= VpcConnectivityProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), clientAuthentication :: Maybe VpcConnectivityClientAuthenticationProperty
clientAuthentication = Maybe VpcConnectivityClientAuthenticationProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties VpcConnectivityProperty where
toResourceProperties :: VpcConnectivityProperty -> ResourceProperties
toResourceProperties VpcConnectivityProperty {Maybe VpcConnectivityClientAuthenticationProperty
()
haddock_workaround_ :: VpcConnectivityProperty -> ()
clientAuthentication :: VpcConnectivityProperty
-> Maybe VpcConnectivityClientAuthenticationProperty
haddock_workaround_ :: ()
clientAuthentication :: Maybe VpcConnectivityClientAuthenticationProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::MSK::Cluster.VpcConnectivity",
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 -> VpcConnectivityClientAuthenticationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ClientAuthentication"
(VpcConnectivityClientAuthenticationProperty -> (Key, Value))
-> Maybe VpcConnectivityClientAuthenticationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe VpcConnectivityClientAuthenticationProperty
clientAuthentication])}
instance JSON.ToJSON VpcConnectivityProperty where
toJSON :: VpcConnectivityProperty -> Value
toJSON VpcConnectivityProperty {Maybe VpcConnectivityClientAuthenticationProperty
()
haddock_workaround_ :: VpcConnectivityProperty -> ()
clientAuthentication :: VpcConnectivityProperty
-> Maybe VpcConnectivityClientAuthenticationProperty
haddock_workaround_ :: ()
clientAuthentication :: Maybe VpcConnectivityClientAuthenticationProperty
..}
= [(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 -> VpcConnectivityClientAuthenticationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ClientAuthentication"
(VpcConnectivityClientAuthenticationProperty -> (Key, Value))
-> Maybe VpcConnectivityClientAuthenticationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe VpcConnectivityClientAuthenticationProperty
clientAuthentication]))
instance Property "ClientAuthentication" VpcConnectivityProperty where
type PropertyType "ClientAuthentication" VpcConnectivityProperty = VpcConnectivityClientAuthenticationProperty
set :: PropertyType "ClientAuthentication" VpcConnectivityProperty
-> VpcConnectivityProperty -> VpcConnectivityProperty
set PropertyType "ClientAuthentication" VpcConnectivityProperty
newValue VpcConnectivityProperty {Maybe VpcConnectivityClientAuthenticationProperty
()
haddock_workaround_ :: VpcConnectivityProperty -> ()
clientAuthentication :: VpcConnectivityProperty
-> Maybe VpcConnectivityClientAuthenticationProperty
haddock_workaround_ :: ()
clientAuthentication :: Maybe VpcConnectivityClientAuthenticationProperty
..}
= VpcConnectivityProperty
{clientAuthentication :: Maybe VpcConnectivityClientAuthenticationProperty
clientAuthentication = VpcConnectivityClientAuthenticationProperty
-> Maybe VpcConnectivityClientAuthenticationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ClientAuthentication" VpcConnectivityProperty
VpcConnectivityClientAuthenticationProperty
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}