module Stratosphere.RTBFabric.ResponderGateway.EksEndpointsConfigurationProperty (
        EksEndpointsConfigurationProperty(..),
        mkEksEndpointsConfigurationProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data EksEndpointsConfigurationProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-rtbfabric-respondergateway-eksendpointsconfiguration.html>
    EksEndpointsConfigurationProperty {EksEndpointsConfigurationProperty -> ()
haddock_workaround_ :: (),
                                       -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-rtbfabric-respondergateway-eksendpointsconfiguration.html#cfn-rtbfabric-respondergateway-eksendpointsconfiguration-clusterapiservercacertificatechain>
                                       EksEndpointsConfigurationProperty -> Value Text
clusterApiServerCaCertificateChain :: (Value Prelude.Text),
                                       -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-rtbfabric-respondergateway-eksendpointsconfiguration.html#cfn-rtbfabric-respondergateway-eksendpointsconfiguration-clusterapiserverendpointuri>
                                       EksEndpointsConfigurationProperty -> Value Text
clusterApiServerEndpointUri :: (Value Prelude.Text),
                                       -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-rtbfabric-respondergateway-eksendpointsconfiguration.html#cfn-rtbfabric-respondergateway-eksendpointsconfiguration-clustername>
                                       EksEndpointsConfigurationProperty -> Value Text
clusterName :: (Value Prelude.Text),
                                       -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-rtbfabric-respondergateway-eksendpointsconfiguration.html#cfn-rtbfabric-respondergateway-eksendpointsconfiguration-endpointsresourcename>
                                       EksEndpointsConfigurationProperty -> Value Text
endpointsResourceName :: (Value Prelude.Text),
                                       -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-rtbfabric-respondergateway-eksendpointsconfiguration.html#cfn-rtbfabric-respondergateway-eksendpointsconfiguration-endpointsresourcenamespace>
                                       EksEndpointsConfigurationProperty -> Value Text
endpointsResourceNamespace :: (Value Prelude.Text),
                                       -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-rtbfabric-respondergateway-eksendpointsconfiguration.html#cfn-rtbfabric-respondergateway-eksendpointsconfiguration-rolearn>
                                       EksEndpointsConfigurationProperty -> Value Text
roleArn :: (Value Prelude.Text)}
  deriving stock (EksEndpointsConfigurationProperty
-> EksEndpointsConfigurationProperty -> Bool
(EksEndpointsConfigurationProperty
 -> EksEndpointsConfigurationProperty -> Bool)
-> (EksEndpointsConfigurationProperty
    -> EksEndpointsConfigurationProperty -> Bool)
-> Eq EksEndpointsConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EksEndpointsConfigurationProperty
-> EksEndpointsConfigurationProperty -> Bool
== :: EksEndpointsConfigurationProperty
-> EksEndpointsConfigurationProperty -> Bool
$c/= :: EksEndpointsConfigurationProperty
-> EksEndpointsConfigurationProperty -> Bool
/= :: EksEndpointsConfigurationProperty
-> EksEndpointsConfigurationProperty -> Bool
Prelude.Eq, Int -> EksEndpointsConfigurationProperty -> ShowS
[EksEndpointsConfigurationProperty] -> ShowS
EksEndpointsConfigurationProperty -> String
(Int -> EksEndpointsConfigurationProperty -> ShowS)
-> (EksEndpointsConfigurationProperty -> String)
-> ([EksEndpointsConfigurationProperty] -> ShowS)
-> Show EksEndpointsConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EksEndpointsConfigurationProperty -> ShowS
showsPrec :: Int -> EksEndpointsConfigurationProperty -> ShowS
$cshow :: EksEndpointsConfigurationProperty -> String
show :: EksEndpointsConfigurationProperty -> String
$cshowList :: [EksEndpointsConfigurationProperty] -> ShowS
showList :: [EksEndpointsConfigurationProperty] -> ShowS
Prelude.Show)
mkEksEndpointsConfigurationProperty ::
  Value Prelude.Text
  -> Value Prelude.Text
     -> Value Prelude.Text
        -> Value Prelude.Text
           -> Value Prelude.Text
              -> Value Prelude.Text -> EksEndpointsConfigurationProperty
mkEksEndpointsConfigurationProperty :: Value Text
-> Value Text
-> Value Text
-> Value Text
-> Value Text
-> Value Text
-> EksEndpointsConfigurationProperty
mkEksEndpointsConfigurationProperty
  Value Text
clusterApiServerCaCertificateChain
  Value Text
clusterApiServerEndpointUri
  Value Text
clusterName
  Value Text
endpointsResourceName
  Value Text
endpointsResourceNamespace
  Value Text
roleArn
  = EksEndpointsConfigurationProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (),
       clusterApiServerCaCertificateChain :: Value Text
clusterApiServerCaCertificateChain = Value Text
clusterApiServerCaCertificateChain,
       clusterApiServerEndpointUri :: Value Text
clusterApiServerEndpointUri = Value Text
clusterApiServerEndpointUri,
       clusterName :: Value Text
clusterName = Value Text
clusterName,
       endpointsResourceName :: Value Text
endpointsResourceName = Value Text
endpointsResourceName,
       endpointsResourceNamespace :: Value Text
endpointsResourceNamespace = Value Text
endpointsResourceNamespace,
       roleArn :: Value Text
roleArn = Value Text
roleArn}
instance ToResourceProperties EksEndpointsConfigurationProperty where
  toResourceProperties :: EksEndpointsConfigurationProperty -> ResourceProperties
toResourceProperties EksEndpointsConfigurationProperty {()
Value Text
haddock_workaround_ :: EksEndpointsConfigurationProperty -> ()
clusterApiServerCaCertificateChain :: EksEndpointsConfigurationProperty -> Value Text
clusterApiServerEndpointUri :: EksEndpointsConfigurationProperty -> Value Text
clusterName :: EksEndpointsConfigurationProperty -> Value Text
endpointsResourceName :: EksEndpointsConfigurationProperty -> Value Text
endpointsResourceNamespace :: EksEndpointsConfigurationProperty -> Value Text
roleArn :: EksEndpointsConfigurationProperty -> Value Text
haddock_workaround_ :: ()
clusterApiServerCaCertificateChain :: Value Text
clusterApiServerEndpointUri :: Value Text
clusterName :: Value Text
endpointsResourceName :: Value Text
endpointsResourceNamespace :: Value Text
roleArn :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::RTBFabric::ResponderGateway.EksEndpointsConfiguration",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"ClusterApiServerCaCertificateChain"
                         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
clusterApiServerCaCertificateChain,
                       Key
"ClusterApiServerEndpointUri" 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
clusterApiServerEndpointUri,
                       Key
"ClusterName" 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
clusterName,
                       Key
"EndpointsResourceName" 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
endpointsResourceName,
                       Key
"EndpointsResourceNamespace" 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
endpointsResourceNamespace,
                       Key
"RoleArn" 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
roleArn]}
instance JSON.ToJSON EksEndpointsConfigurationProperty where
  toJSON :: EksEndpointsConfigurationProperty -> Value
toJSON EksEndpointsConfigurationProperty {()
Value Text
haddock_workaround_ :: EksEndpointsConfigurationProperty -> ()
clusterApiServerCaCertificateChain :: EksEndpointsConfigurationProperty -> Value Text
clusterApiServerEndpointUri :: EksEndpointsConfigurationProperty -> Value Text
clusterName :: EksEndpointsConfigurationProperty -> Value Text
endpointsResourceName :: EksEndpointsConfigurationProperty -> Value Text
endpointsResourceNamespace :: EksEndpointsConfigurationProperty -> Value Text
roleArn :: EksEndpointsConfigurationProperty -> Value Text
haddock_workaround_ :: ()
clusterApiServerCaCertificateChain :: Value Text
clusterApiServerEndpointUri :: Value Text
clusterName :: Value Text
endpointsResourceName :: Value Text
endpointsResourceNamespace :: Value Text
roleArn :: Value Text
..}
    = [(Key, Value)] -> Value
JSON.object
        [Key
"ClusterApiServerCaCertificateChain"
           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
clusterApiServerCaCertificateChain,
         Key
"ClusterApiServerEndpointUri" 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
clusterApiServerEndpointUri,
         Key
"ClusterName" 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
clusterName,
         Key
"EndpointsResourceName" 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
endpointsResourceName,
         Key
"EndpointsResourceNamespace" 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
endpointsResourceNamespace,
         Key
"RoleArn" 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
roleArn]
instance Property "ClusterApiServerCaCertificateChain" EksEndpointsConfigurationProperty where
  type PropertyType "ClusterApiServerCaCertificateChain" EksEndpointsConfigurationProperty = Value Prelude.Text
  set :: PropertyType
  "ClusterApiServerCaCertificateChain"
  EksEndpointsConfigurationProperty
-> EksEndpointsConfigurationProperty
-> EksEndpointsConfigurationProperty
set PropertyType
  "ClusterApiServerCaCertificateChain"
  EksEndpointsConfigurationProperty
newValue EksEndpointsConfigurationProperty {()
Value Text
haddock_workaround_ :: EksEndpointsConfigurationProperty -> ()
clusterApiServerCaCertificateChain :: EksEndpointsConfigurationProperty -> Value Text
clusterApiServerEndpointUri :: EksEndpointsConfigurationProperty -> Value Text
clusterName :: EksEndpointsConfigurationProperty -> Value Text
endpointsResourceName :: EksEndpointsConfigurationProperty -> Value Text
endpointsResourceNamespace :: EksEndpointsConfigurationProperty -> Value Text
roleArn :: EksEndpointsConfigurationProperty -> Value Text
haddock_workaround_ :: ()
clusterApiServerCaCertificateChain :: Value Text
clusterApiServerEndpointUri :: Value Text
clusterName :: Value Text
endpointsResourceName :: Value Text
endpointsResourceNamespace :: Value Text
roleArn :: Value Text
..}
    = EksEndpointsConfigurationProperty
        {clusterApiServerCaCertificateChain :: Value Text
clusterApiServerCaCertificateChain = PropertyType
  "ClusterApiServerCaCertificateChain"
  EksEndpointsConfigurationProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
clusterApiServerEndpointUri :: Value Text
clusterName :: Value Text
endpointsResourceName :: Value Text
endpointsResourceNamespace :: Value Text
roleArn :: Value Text
haddock_workaround_ :: ()
clusterApiServerEndpointUri :: Value Text
clusterName :: Value Text
endpointsResourceName :: Value Text
endpointsResourceNamespace :: Value Text
roleArn :: Value Text
..}
instance Property "ClusterApiServerEndpointUri" EksEndpointsConfigurationProperty where
  type PropertyType "ClusterApiServerEndpointUri" EksEndpointsConfigurationProperty = Value Prelude.Text
  set :: PropertyType
  "ClusterApiServerEndpointUri" EksEndpointsConfigurationProperty
-> EksEndpointsConfigurationProperty
-> EksEndpointsConfigurationProperty
set PropertyType
  "ClusterApiServerEndpointUri" EksEndpointsConfigurationProperty
newValue EksEndpointsConfigurationProperty {()
Value Text
haddock_workaround_ :: EksEndpointsConfigurationProperty -> ()
clusterApiServerCaCertificateChain :: EksEndpointsConfigurationProperty -> Value Text
clusterApiServerEndpointUri :: EksEndpointsConfigurationProperty -> Value Text
clusterName :: EksEndpointsConfigurationProperty -> Value Text
endpointsResourceName :: EksEndpointsConfigurationProperty -> Value Text
endpointsResourceNamespace :: EksEndpointsConfigurationProperty -> Value Text
roleArn :: EksEndpointsConfigurationProperty -> Value Text
haddock_workaround_ :: ()
clusterApiServerCaCertificateChain :: Value Text
clusterApiServerEndpointUri :: Value Text
clusterName :: Value Text
endpointsResourceName :: Value Text
endpointsResourceNamespace :: Value Text
roleArn :: Value Text
..}
    = EksEndpointsConfigurationProperty
        {clusterApiServerEndpointUri :: Value Text
clusterApiServerEndpointUri = PropertyType
  "ClusterApiServerEndpointUri" EksEndpointsConfigurationProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
clusterApiServerCaCertificateChain :: Value Text
clusterName :: Value Text
endpointsResourceName :: Value Text
endpointsResourceNamespace :: Value Text
roleArn :: Value Text
haddock_workaround_ :: ()
clusterApiServerCaCertificateChain :: Value Text
clusterName :: Value Text
endpointsResourceName :: Value Text
endpointsResourceNamespace :: Value Text
roleArn :: Value Text
..}
instance Property "ClusterName" EksEndpointsConfigurationProperty where
  type PropertyType "ClusterName" EksEndpointsConfigurationProperty = Value Prelude.Text
  set :: PropertyType "ClusterName" EksEndpointsConfigurationProperty
-> EksEndpointsConfigurationProperty
-> EksEndpointsConfigurationProperty
set PropertyType "ClusterName" EksEndpointsConfigurationProperty
newValue EksEndpointsConfigurationProperty {()
Value Text
haddock_workaround_ :: EksEndpointsConfigurationProperty -> ()
clusterApiServerCaCertificateChain :: EksEndpointsConfigurationProperty -> Value Text
clusterApiServerEndpointUri :: EksEndpointsConfigurationProperty -> Value Text
clusterName :: EksEndpointsConfigurationProperty -> Value Text
endpointsResourceName :: EksEndpointsConfigurationProperty -> Value Text
endpointsResourceNamespace :: EksEndpointsConfigurationProperty -> Value Text
roleArn :: EksEndpointsConfigurationProperty -> Value Text
haddock_workaround_ :: ()
clusterApiServerCaCertificateChain :: Value Text
clusterApiServerEndpointUri :: Value Text
clusterName :: Value Text
endpointsResourceName :: Value Text
endpointsResourceNamespace :: Value Text
roleArn :: Value Text
..}
    = EksEndpointsConfigurationProperty {clusterName :: Value Text
clusterName = PropertyType "ClusterName" EksEndpointsConfigurationProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
clusterApiServerCaCertificateChain :: Value Text
clusterApiServerEndpointUri :: Value Text
endpointsResourceName :: Value Text
endpointsResourceNamespace :: Value Text
roleArn :: Value Text
haddock_workaround_ :: ()
clusterApiServerCaCertificateChain :: Value Text
clusterApiServerEndpointUri :: Value Text
endpointsResourceName :: Value Text
endpointsResourceNamespace :: Value Text
roleArn :: Value Text
..}
instance Property "EndpointsResourceName" EksEndpointsConfigurationProperty where
  type PropertyType "EndpointsResourceName" EksEndpointsConfigurationProperty = Value Prelude.Text
  set :: PropertyType
  "EndpointsResourceName" EksEndpointsConfigurationProperty
-> EksEndpointsConfigurationProperty
-> EksEndpointsConfigurationProperty
set PropertyType
  "EndpointsResourceName" EksEndpointsConfigurationProperty
newValue EksEndpointsConfigurationProperty {()
Value Text
haddock_workaround_ :: EksEndpointsConfigurationProperty -> ()
clusterApiServerCaCertificateChain :: EksEndpointsConfigurationProperty -> Value Text
clusterApiServerEndpointUri :: EksEndpointsConfigurationProperty -> Value Text
clusterName :: EksEndpointsConfigurationProperty -> Value Text
endpointsResourceName :: EksEndpointsConfigurationProperty -> Value Text
endpointsResourceNamespace :: EksEndpointsConfigurationProperty -> Value Text
roleArn :: EksEndpointsConfigurationProperty -> Value Text
haddock_workaround_ :: ()
clusterApiServerCaCertificateChain :: Value Text
clusterApiServerEndpointUri :: Value Text
clusterName :: Value Text
endpointsResourceName :: Value Text
endpointsResourceNamespace :: Value Text
roleArn :: Value Text
..}
    = EksEndpointsConfigurationProperty
        {endpointsResourceName :: Value Text
endpointsResourceName = PropertyType
  "EndpointsResourceName" EksEndpointsConfigurationProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
clusterApiServerCaCertificateChain :: Value Text
clusterApiServerEndpointUri :: Value Text
clusterName :: Value Text
endpointsResourceNamespace :: Value Text
roleArn :: Value Text
haddock_workaround_ :: ()
clusterApiServerCaCertificateChain :: Value Text
clusterApiServerEndpointUri :: Value Text
clusterName :: Value Text
endpointsResourceNamespace :: Value Text
roleArn :: Value Text
..}
instance Property "EndpointsResourceNamespace" EksEndpointsConfigurationProperty where
  type PropertyType "EndpointsResourceNamespace" EksEndpointsConfigurationProperty = Value Prelude.Text
  set :: PropertyType
  "EndpointsResourceNamespace" EksEndpointsConfigurationProperty
-> EksEndpointsConfigurationProperty
-> EksEndpointsConfigurationProperty
set PropertyType
  "EndpointsResourceNamespace" EksEndpointsConfigurationProperty
newValue EksEndpointsConfigurationProperty {()
Value Text
haddock_workaround_ :: EksEndpointsConfigurationProperty -> ()
clusterApiServerCaCertificateChain :: EksEndpointsConfigurationProperty -> Value Text
clusterApiServerEndpointUri :: EksEndpointsConfigurationProperty -> Value Text
clusterName :: EksEndpointsConfigurationProperty -> Value Text
endpointsResourceName :: EksEndpointsConfigurationProperty -> Value Text
endpointsResourceNamespace :: EksEndpointsConfigurationProperty -> Value Text
roleArn :: EksEndpointsConfigurationProperty -> Value Text
haddock_workaround_ :: ()
clusterApiServerCaCertificateChain :: Value Text
clusterApiServerEndpointUri :: Value Text
clusterName :: Value Text
endpointsResourceName :: Value Text
endpointsResourceNamespace :: Value Text
roleArn :: Value Text
..}
    = EksEndpointsConfigurationProperty
        {endpointsResourceNamespace :: Value Text
endpointsResourceNamespace = PropertyType
  "EndpointsResourceNamespace" EksEndpointsConfigurationProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
clusterApiServerCaCertificateChain :: Value Text
clusterApiServerEndpointUri :: Value Text
clusterName :: Value Text
endpointsResourceName :: Value Text
roleArn :: Value Text
haddock_workaround_ :: ()
clusterApiServerCaCertificateChain :: Value Text
clusterApiServerEndpointUri :: Value Text
clusterName :: Value Text
endpointsResourceName :: Value Text
roleArn :: Value Text
..}
instance Property "RoleArn" EksEndpointsConfigurationProperty where
  type PropertyType "RoleArn" EksEndpointsConfigurationProperty = Value Prelude.Text
  set :: PropertyType "RoleArn" EksEndpointsConfigurationProperty
-> EksEndpointsConfigurationProperty
-> EksEndpointsConfigurationProperty
set PropertyType "RoleArn" EksEndpointsConfigurationProperty
newValue EksEndpointsConfigurationProperty {()
Value Text
haddock_workaround_ :: EksEndpointsConfigurationProperty -> ()
clusterApiServerCaCertificateChain :: EksEndpointsConfigurationProperty -> Value Text
clusterApiServerEndpointUri :: EksEndpointsConfigurationProperty -> Value Text
clusterName :: EksEndpointsConfigurationProperty -> Value Text
endpointsResourceName :: EksEndpointsConfigurationProperty -> Value Text
endpointsResourceNamespace :: EksEndpointsConfigurationProperty -> Value Text
roleArn :: EksEndpointsConfigurationProperty -> Value Text
haddock_workaround_ :: ()
clusterApiServerCaCertificateChain :: Value Text
clusterApiServerEndpointUri :: Value Text
clusterName :: Value Text
endpointsResourceName :: Value Text
endpointsResourceNamespace :: Value Text
roleArn :: Value Text
..}
    = EksEndpointsConfigurationProperty {roleArn :: Value Text
roleArn = PropertyType "RoleArn" EksEndpointsConfigurationProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
clusterApiServerCaCertificateChain :: Value Text
clusterApiServerEndpointUri :: Value Text
clusterName :: Value Text
endpointsResourceName :: Value Text
endpointsResourceNamespace :: Value Text
haddock_workaround_ :: ()
clusterApiServerCaCertificateChain :: Value Text
clusterApiServerEndpointUri :: Value Text
clusterName :: Value Text
endpointsResourceName :: Value Text
endpointsResourceNamespace :: Value Text
..}