module Stratosphere.MSK.ServerlessCluster.IamProperty (
        IamProperty(..), mkIamProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data IamProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-msk-serverlesscluster-iam.html>
    IamProperty {IamProperty -> ()
haddock_workaround_ :: (),
                 -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-msk-serverlesscluster-iam.html#cfn-msk-serverlesscluster-iam-enabled>
                 IamProperty -> Value Bool
enabled :: (Value Prelude.Bool)}
  deriving stock (IamProperty -> IamProperty -> Bool
(IamProperty -> IamProperty -> Bool)
-> (IamProperty -> IamProperty -> Bool) -> Eq IamProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IamProperty -> IamProperty -> Bool
== :: IamProperty -> IamProperty -> Bool
$c/= :: IamProperty -> IamProperty -> Bool
/= :: IamProperty -> IamProperty -> Bool
Prelude.Eq, Int -> IamProperty -> ShowS
[IamProperty] -> ShowS
IamProperty -> String
(Int -> IamProperty -> ShowS)
-> (IamProperty -> String)
-> ([IamProperty] -> ShowS)
-> Show IamProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IamProperty -> ShowS
showsPrec :: Int -> IamProperty -> ShowS
$cshow :: IamProperty -> String
show :: IamProperty -> String
$cshowList :: [IamProperty] -> ShowS
showList :: [IamProperty] -> ShowS
Prelude.Show)
mkIamProperty :: Value Prelude.Bool -> IamProperty
mkIamProperty :: Value Bool -> IamProperty
mkIamProperty Value Bool
enabled
  = IamProperty {haddock_workaround_ :: ()
haddock_workaround_ = (), enabled :: Value Bool
enabled = Value Bool
enabled}
instance ToResourceProperties IamProperty where
  toResourceProperties :: IamProperty -> ResourceProperties
toResourceProperties IamProperty {()
Value Bool
haddock_workaround_ :: IamProperty -> ()
enabled :: IamProperty -> Value Bool
haddock_workaround_ :: ()
enabled :: Value Bool
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::MSK::ServerlessCluster.Iam",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"Enabled" Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Bool
enabled]}
instance JSON.ToJSON IamProperty where
  toJSON :: IamProperty -> Value
toJSON IamProperty {()
Value Bool
haddock_workaround_ :: IamProperty -> ()
enabled :: IamProperty -> Value Bool
haddock_workaround_ :: ()
enabled :: Value Bool
..} = [(Key, Value)] -> Value
JSON.object [Key
"Enabled" Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Bool
enabled]
instance Property "Enabled" IamProperty where
  type PropertyType "Enabled" IamProperty = Value Prelude.Bool
  set :: PropertyType "Enabled" IamProperty -> IamProperty -> IamProperty
set PropertyType "Enabled" IamProperty
newValue IamProperty {()
Value Bool
haddock_workaround_ :: IamProperty -> ()
enabled :: IamProperty -> Value Bool
haddock_workaround_ :: ()
enabled :: Value Bool
..}
    = IamProperty {enabled :: Value Bool
enabled = PropertyType "Enabled" IamProperty
Value Bool
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}