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