module Stratosphere.KafkaConnect.Connector.PluginProperty (
        module Exports, PluginProperty(..), mkPluginProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.KafkaConnect.Connector.CustomPluginProperty as Exports
import Stratosphere.ResourceProperties
data PluginProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kafkaconnect-connector-plugin.html>
    PluginProperty {PluginProperty -> ()
haddock_workaround_ :: (),
                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kafkaconnect-connector-plugin.html#cfn-kafkaconnect-connector-plugin-customplugin>
                    PluginProperty -> CustomPluginProperty
customPlugin :: CustomPluginProperty}
  deriving stock (PluginProperty -> PluginProperty -> Bool
(PluginProperty -> PluginProperty -> Bool)
-> (PluginProperty -> PluginProperty -> Bool) -> Eq PluginProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PluginProperty -> PluginProperty -> Bool
== :: PluginProperty -> PluginProperty -> Bool
$c/= :: PluginProperty -> PluginProperty -> Bool
/= :: PluginProperty -> PluginProperty -> Bool
Prelude.Eq, Int -> PluginProperty -> ShowS
[PluginProperty] -> ShowS
PluginProperty -> String
(Int -> PluginProperty -> ShowS)
-> (PluginProperty -> String)
-> ([PluginProperty] -> ShowS)
-> Show PluginProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PluginProperty -> ShowS
showsPrec :: Int -> PluginProperty -> ShowS
$cshow :: PluginProperty -> String
show :: PluginProperty -> String
$cshowList :: [PluginProperty] -> ShowS
showList :: [PluginProperty] -> ShowS
Prelude.Show)
mkPluginProperty :: CustomPluginProperty -> PluginProperty
mkPluginProperty :: CustomPluginProperty -> PluginProperty
mkPluginProperty CustomPluginProperty
customPlugin
  = PluginProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), customPlugin :: CustomPluginProperty
customPlugin = CustomPluginProperty
customPlugin}
instance ToResourceProperties PluginProperty where
  toResourceProperties :: PluginProperty -> ResourceProperties
toResourceProperties PluginProperty {()
CustomPluginProperty
haddock_workaround_ :: PluginProperty -> ()
customPlugin :: PluginProperty -> CustomPluginProperty
haddock_workaround_ :: ()
customPlugin :: CustomPluginProperty
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::KafkaConnect::Connector.Plugin",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"CustomPlugin" Key -> CustomPluginProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= CustomPluginProperty
customPlugin]}
instance JSON.ToJSON PluginProperty where
  toJSON :: PluginProperty -> Value
toJSON PluginProperty {()
CustomPluginProperty
haddock_workaround_ :: PluginProperty -> ()
customPlugin :: PluginProperty -> CustomPluginProperty
haddock_workaround_ :: ()
customPlugin :: CustomPluginProperty
..}
    = [(Key, Value)] -> Value
JSON.object [Key
"CustomPlugin" Key -> CustomPluginProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= CustomPluginProperty
customPlugin]
instance Property "CustomPlugin" PluginProperty where
  type PropertyType "CustomPlugin" PluginProperty = CustomPluginProperty
  set :: PropertyType "CustomPlugin" PluginProperty
-> PluginProperty -> PluginProperty
set PropertyType "CustomPlugin" PluginProperty
newValue PluginProperty {()
CustomPluginProperty
haddock_workaround_ :: PluginProperty -> ()
customPlugin :: PluginProperty -> CustomPluginProperty
haddock_workaround_ :: ()
customPlugin :: CustomPluginProperty
..}
    = PluginProperty {customPlugin :: CustomPluginProperty
customPlugin = PropertyType "CustomPlugin" PluginProperty
CustomPluginProperty
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}