module Stratosphere.Bedrock.KnowledgeBase.RedshiftQueryEngineConfigurationProperty (
        module Exports, RedshiftQueryEngineConfigurationProperty(..),
        mkRedshiftQueryEngineConfigurationProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Bedrock.KnowledgeBase.RedshiftProvisionedConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.Bedrock.KnowledgeBase.RedshiftServerlessConfigurationProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data RedshiftQueryEngineConfigurationProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-bedrock-knowledgebase-redshiftqueryengineconfiguration.html>
    RedshiftQueryEngineConfigurationProperty {RedshiftQueryEngineConfigurationProperty -> ()
haddock_workaround_ :: (),
                                              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-bedrock-knowledgebase-redshiftqueryengineconfiguration.html#cfn-bedrock-knowledgebase-redshiftqueryengineconfiguration-provisionedconfiguration>
                                              RedshiftQueryEngineConfigurationProperty
-> Maybe RedshiftProvisionedConfigurationProperty
provisionedConfiguration :: (Prelude.Maybe RedshiftProvisionedConfigurationProperty),
                                              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-bedrock-knowledgebase-redshiftqueryengineconfiguration.html#cfn-bedrock-knowledgebase-redshiftqueryengineconfiguration-serverlessconfiguration>
                                              RedshiftQueryEngineConfigurationProperty
-> Maybe RedshiftServerlessConfigurationProperty
serverlessConfiguration :: (Prelude.Maybe RedshiftServerlessConfigurationProperty),
                                              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-bedrock-knowledgebase-redshiftqueryengineconfiguration.html#cfn-bedrock-knowledgebase-redshiftqueryengineconfiguration-type>
                                              RedshiftQueryEngineConfigurationProperty -> Value Text
type' :: (Value Prelude.Text)}
  deriving stock (RedshiftQueryEngineConfigurationProperty
-> RedshiftQueryEngineConfigurationProperty -> Bool
(RedshiftQueryEngineConfigurationProperty
 -> RedshiftQueryEngineConfigurationProperty -> Bool)
-> (RedshiftQueryEngineConfigurationProperty
    -> RedshiftQueryEngineConfigurationProperty -> Bool)
-> Eq RedshiftQueryEngineConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RedshiftQueryEngineConfigurationProperty
-> RedshiftQueryEngineConfigurationProperty -> Bool
== :: RedshiftQueryEngineConfigurationProperty
-> RedshiftQueryEngineConfigurationProperty -> Bool
$c/= :: RedshiftQueryEngineConfigurationProperty
-> RedshiftQueryEngineConfigurationProperty -> Bool
/= :: RedshiftQueryEngineConfigurationProperty
-> RedshiftQueryEngineConfigurationProperty -> Bool
Prelude.Eq, Int -> RedshiftQueryEngineConfigurationProperty -> ShowS
[RedshiftQueryEngineConfigurationProperty] -> ShowS
RedshiftQueryEngineConfigurationProperty -> String
(Int -> RedshiftQueryEngineConfigurationProperty -> ShowS)
-> (RedshiftQueryEngineConfigurationProperty -> String)
-> ([RedshiftQueryEngineConfigurationProperty] -> ShowS)
-> Show RedshiftQueryEngineConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RedshiftQueryEngineConfigurationProperty -> ShowS
showsPrec :: Int -> RedshiftQueryEngineConfigurationProperty -> ShowS
$cshow :: RedshiftQueryEngineConfigurationProperty -> String
show :: RedshiftQueryEngineConfigurationProperty -> String
$cshowList :: [RedshiftQueryEngineConfigurationProperty] -> ShowS
showList :: [RedshiftQueryEngineConfigurationProperty] -> ShowS
Prelude.Show)
mkRedshiftQueryEngineConfigurationProperty ::
  Value Prelude.Text -> RedshiftQueryEngineConfigurationProperty
mkRedshiftQueryEngineConfigurationProperty :: Value Text -> RedshiftQueryEngineConfigurationProperty
mkRedshiftQueryEngineConfigurationProperty Value Text
type'
  = RedshiftQueryEngineConfigurationProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), type' :: Value Text
type' = Value Text
type',
       provisionedConfiguration :: Maybe RedshiftProvisionedConfigurationProperty
provisionedConfiguration = Maybe RedshiftProvisionedConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
       serverlessConfiguration :: Maybe RedshiftServerlessConfigurationProperty
serverlessConfiguration = Maybe RedshiftServerlessConfigurationProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties RedshiftQueryEngineConfigurationProperty where
  toResourceProperties :: RedshiftQueryEngineConfigurationProperty -> ResourceProperties
toResourceProperties RedshiftQueryEngineConfigurationProperty {Maybe RedshiftProvisionedConfigurationProperty
Maybe RedshiftServerlessConfigurationProperty
()
Value Text
haddock_workaround_ :: RedshiftQueryEngineConfigurationProperty -> ()
provisionedConfiguration :: RedshiftQueryEngineConfigurationProperty
-> Maybe RedshiftProvisionedConfigurationProperty
serverlessConfiguration :: RedshiftQueryEngineConfigurationProperty
-> Maybe RedshiftServerlessConfigurationProperty
type' :: RedshiftQueryEngineConfigurationProperty -> Value Text
haddock_workaround_ :: ()
provisionedConfiguration :: Maybe RedshiftProvisionedConfigurationProperty
serverlessConfiguration :: Maybe RedshiftServerlessConfigurationProperty
type' :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::Bedrock::KnowledgeBase.RedshiftQueryEngineConfiguration",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
                        ([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
                           [Key
"Type" 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
type']
                           ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                              [Key -> RedshiftProvisionedConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ProvisionedConfiguration"
                                 (RedshiftProvisionedConfigurationProperty -> (Key, Value))
-> Maybe RedshiftProvisionedConfigurationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe RedshiftProvisionedConfigurationProperty
provisionedConfiguration,
                               Key -> RedshiftServerlessConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ServerlessConfiguration"
                                 (RedshiftServerlessConfigurationProperty -> (Key, Value))
-> Maybe RedshiftServerlessConfigurationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe RedshiftServerlessConfigurationProperty
serverlessConfiguration]))}
instance JSON.ToJSON RedshiftQueryEngineConfigurationProperty where
  toJSON :: RedshiftQueryEngineConfigurationProperty -> Value
toJSON RedshiftQueryEngineConfigurationProperty {Maybe RedshiftProvisionedConfigurationProperty
Maybe RedshiftServerlessConfigurationProperty
()
Value Text
haddock_workaround_ :: RedshiftQueryEngineConfigurationProperty -> ()
provisionedConfiguration :: RedshiftQueryEngineConfigurationProperty
-> Maybe RedshiftProvisionedConfigurationProperty
serverlessConfiguration :: RedshiftQueryEngineConfigurationProperty
-> Maybe RedshiftServerlessConfigurationProperty
type' :: RedshiftQueryEngineConfigurationProperty -> Value Text
haddock_workaround_ :: ()
provisionedConfiguration :: Maybe RedshiftProvisionedConfigurationProperty
serverlessConfiguration :: Maybe RedshiftServerlessConfigurationProperty
type' :: Value Text
..}
    = [(Key, Value)] -> Value
JSON.object
        ([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
           ([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
              [Key
"Type" 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
type']
              ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                 [Key -> RedshiftProvisionedConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ProvisionedConfiguration"
                    (RedshiftProvisionedConfigurationProperty -> (Key, Value))
-> Maybe RedshiftProvisionedConfigurationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe RedshiftProvisionedConfigurationProperty
provisionedConfiguration,
                  Key -> RedshiftServerlessConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ServerlessConfiguration"
                    (RedshiftServerlessConfigurationProperty -> (Key, Value))
-> Maybe RedshiftServerlessConfigurationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe RedshiftServerlessConfigurationProperty
serverlessConfiguration])))
instance Property "ProvisionedConfiguration" RedshiftQueryEngineConfigurationProperty where
  type PropertyType "ProvisionedConfiguration" RedshiftQueryEngineConfigurationProperty = RedshiftProvisionedConfigurationProperty
  set :: PropertyType
  "ProvisionedConfiguration" RedshiftQueryEngineConfigurationProperty
-> RedshiftQueryEngineConfigurationProperty
-> RedshiftQueryEngineConfigurationProperty
set PropertyType
  "ProvisionedConfiguration" RedshiftQueryEngineConfigurationProperty
newValue RedshiftQueryEngineConfigurationProperty {Maybe RedshiftProvisionedConfigurationProperty
Maybe RedshiftServerlessConfigurationProperty
()
Value Text
haddock_workaround_ :: RedshiftQueryEngineConfigurationProperty -> ()
provisionedConfiguration :: RedshiftQueryEngineConfigurationProperty
-> Maybe RedshiftProvisionedConfigurationProperty
serverlessConfiguration :: RedshiftQueryEngineConfigurationProperty
-> Maybe RedshiftServerlessConfigurationProperty
type' :: RedshiftQueryEngineConfigurationProperty -> Value Text
haddock_workaround_ :: ()
provisionedConfiguration :: Maybe RedshiftProvisionedConfigurationProperty
serverlessConfiguration :: Maybe RedshiftServerlessConfigurationProperty
type' :: Value Text
..}
    = RedshiftQueryEngineConfigurationProperty
        {provisionedConfiguration :: Maybe RedshiftProvisionedConfigurationProperty
provisionedConfiguration = RedshiftProvisionedConfigurationProperty
-> Maybe RedshiftProvisionedConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "ProvisionedConfiguration" RedshiftQueryEngineConfigurationProperty
RedshiftProvisionedConfigurationProperty
newValue, Maybe RedshiftServerlessConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
serverlessConfiguration :: Maybe RedshiftServerlessConfigurationProperty
type' :: Value Text
haddock_workaround_ :: ()
serverlessConfiguration :: Maybe RedshiftServerlessConfigurationProperty
type' :: Value Text
..}
instance Property "ServerlessConfiguration" RedshiftQueryEngineConfigurationProperty where
  type PropertyType "ServerlessConfiguration" RedshiftQueryEngineConfigurationProperty = RedshiftServerlessConfigurationProperty
  set :: PropertyType
  "ServerlessConfiguration" RedshiftQueryEngineConfigurationProperty
-> RedshiftQueryEngineConfigurationProperty
-> RedshiftQueryEngineConfigurationProperty
set PropertyType
  "ServerlessConfiguration" RedshiftQueryEngineConfigurationProperty
newValue RedshiftQueryEngineConfigurationProperty {Maybe RedshiftProvisionedConfigurationProperty
Maybe RedshiftServerlessConfigurationProperty
()
Value Text
haddock_workaround_ :: RedshiftQueryEngineConfigurationProperty -> ()
provisionedConfiguration :: RedshiftQueryEngineConfigurationProperty
-> Maybe RedshiftProvisionedConfigurationProperty
serverlessConfiguration :: RedshiftQueryEngineConfigurationProperty
-> Maybe RedshiftServerlessConfigurationProperty
type' :: RedshiftQueryEngineConfigurationProperty -> Value Text
haddock_workaround_ :: ()
provisionedConfiguration :: Maybe RedshiftProvisionedConfigurationProperty
serverlessConfiguration :: Maybe RedshiftServerlessConfigurationProperty
type' :: Value Text
..}
    = RedshiftQueryEngineConfigurationProperty
        {serverlessConfiguration :: Maybe RedshiftServerlessConfigurationProperty
serverlessConfiguration = RedshiftServerlessConfigurationProperty
-> Maybe RedshiftServerlessConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "ServerlessConfiguration" RedshiftQueryEngineConfigurationProperty
RedshiftServerlessConfigurationProperty
newValue, Maybe RedshiftProvisionedConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
provisionedConfiguration :: Maybe RedshiftProvisionedConfigurationProperty
type' :: Value Text
haddock_workaround_ :: ()
provisionedConfiguration :: Maybe RedshiftProvisionedConfigurationProperty
type' :: Value Text
..}
instance Property "Type" RedshiftQueryEngineConfigurationProperty where
  type PropertyType "Type" RedshiftQueryEngineConfigurationProperty = Value Prelude.Text
  set :: PropertyType "Type" RedshiftQueryEngineConfigurationProperty
-> RedshiftQueryEngineConfigurationProperty
-> RedshiftQueryEngineConfigurationProperty
set PropertyType "Type" RedshiftQueryEngineConfigurationProperty
newValue RedshiftQueryEngineConfigurationProperty {Maybe RedshiftProvisionedConfigurationProperty
Maybe RedshiftServerlessConfigurationProperty
()
Value Text
haddock_workaround_ :: RedshiftQueryEngineConfigurationProperty -> ()
provisionedConfiguration :: RedshiftQueryEngineConfigurationProperty
-> Maybe RedshiftProvisionedConfigurationProperty
serverlessConfiguration :: RedshiftQueryEngineConfigurationProperty
-> Maybe RedshiftServerlessConfigurationProperty
type' :: RedshiftQueryEngineConfigurationProperty -> Value Text
haddock_workaround_ :: ()
provisionedConfiguration :: Maybe RedshiftProvisionedConfigurationProperty
serverlessConfiguration :: Maybe RedshiftServerlessConfigurationProperty
type' :: Value Text
..}
    = RedshiftQueryEngineConfigurationProperty {type' :: Value Text
type' = PropertyType "Type" RedshiftQueryEngineConfigurationProperty
Value Text
newValue, Maybe RedshiftProvisionedConfigurationProperty
Maybe RedshiftServerlessConfigurationProperty
()
haddock_workaround_ :: ()
provisionedConfiguration :: Maybe RedshiftProvisionedConfigurationProperty
serverlessConfiguration :: Maybe RedshiftServerlessConfigurationProperty
haddock_workaround_ :: ()
provisionedConfiguration :: Maybe RedshiftProvisionedConfigurationProperty
serverlessConfiguration :: Maybe RedshiftServerlessConfigurationProperty
..}