module Stratosphere.Lex.Bot.QnAIntentConfigurationProperty (
        module Exports, QnAIntentConfigurationProperty(..),
        mkQnAIntentConfigurationProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Lex.Bot.BedrockModelSpecificationProperty as Exports
import {-# SOURCE #-} Stratosphere.Lex.Bot.DataSourceConfigurationProperty as Exports
import Stratosphere.ResourceProperties
data QnAIntentConfigurationProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-lex-bot-qnaintentconfiguration.html>
    QnAIntentConfigurationProperty {QnAIntentConfigurationProperty -> ()
haddock_workaround_ :: (),
                                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-lex-bot-qnaintentconfiguration.html#cfn-lex-bot-qnaintentconfiguration-bedrockmodelconfiguration>
                                    QnAIntentConfigurationProperty -> BedrockModelSpecificationProperty
bedrockModelConfiguration :: BedrockModelSpecificationProperty,
                                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-lex-bot-qnaintentconfiguration.html#cfn-lex-bot-qnaintentconfiguration-datasourceconfiguration>
                                    QnAIntentConfigurationProperty -> DataSourceConfigurationProperty
dataSourceConfiguration :: DataSourceConfigurationProperty}
  deriving stock (QnAIntentConfigurationProperty
-> QnAIntentConfigurationProperty -> Bool
(QnAIntentConfigurationProperty
 -> QnAIntentConfigurationProperty -> Bool)
-> (QnAIntentConfigurationProperty
    -> QnAIntentConfigurationProperty -> Bool)
-> Eq QnAIntentConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: QnAIntentConfigurationProperty
-> QnAIntentConfigurationProperty -> Bool
== :: QnAIntentConfigurationProperty
-> QnAIntentConfigurationProperty -> Bool
$c/= :: QnAIntentConfigurationProperty
-> QnAIntentConfigurationProperty -> Bool
/= :: QnAIntentConfigurationProperty
-> QnAIntentConfigurationProperty -> Bool
Prelude.Eq, Int -> QnAIntentConfigurationProperty -> ShowS
[QnAIntentConfigurationProperty] -> ShowS
QnAIntentConfigurationProperty -> String
(Int -> QnAIntentConfigurationProperty -> ShowS)
-> (QnAIntentConfigurationProperty -> String)
-> ([QnAIntentConfigurationProperty] -> ShowS)
-> Show QnAIntentConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> QnAIntentConfigurationProperty -> ShowS
showsPrec :: Int -> QnAIntentConfigurationProperty -> ShowS
$cshow :: QnAIntentConfigurationProperty -> String
show :: QnAIntentConfigurationProperty -> String
$cshowList :: [QnAIntentConfigurationProperty] -> ShowS
showList :: [QnAIntentConfigurationProperty] -> ShowS
Prelude.Show)
mkQnAIntentConfigurationProperty ::
  BedrockModelSpecificationProperty
  -> DataSourceConfigurationProperty
     -> QnAIntentConfigurationProperty
mkQnAIntentConfigurationProperty :: BedrockModelSpecificationProperty
-> DataSourceConfigurationProperty
-> QnAIntentConfigurationProperty
mkQnAIntentConfigurationProperty
  BedrockModelSpecificationProperty
bedrockModelConfiguration
  DataSourceConfigurationProperty
dataSourceConfiguration
  = QnAIntentConfigurationProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (),
       bedrockModelConfiguration :: BedrockModelSpecificationProperty
bedrockModelConfiguration = BedrockModelSpecificationProperty
bedrockModelConfiguration,
       dataSourceConfiguration :: DataSourceConfigurationProperty
dataSourceConfiguration = DataSourceConfigurationProperty
dataSourceConfiguration}
instance ToResourceProperties QnAIntentConfigurationProperty where
  toResourceProperties :: QnAIntentConfigurationProperty -> ResourceProperties
toResourceProperties QnAIntentConfigurationProperty {()
BedrockModelSpecificationProperty
DataSourceConfigurationProperty
haddock_workaround_ :: QnAIntentConfigurationProperty -> ()
bedrockModelConfiguration :: QnAIntentConfigurationProperty -> BedrockModelSpecificationProperty
dataSourceConfiguration :: QnAIntentConfigurationProperty -> DataSourceConfigurationProperty
haddock_workaround_ :: ()
bedrockModelConfiguration :: BedrockModelSpecificationProperty
dataSourceConfiguration :: DataSourceConfigurationProperty
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::Lex::Bot.QnAIntentConfiguration",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"BedrockModelConfiguration"
                         Key -> BedrockModelSpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= BedrockModelSpecificationProperty
bedrockModelConfiguration,
                       Key
"DataSourceConfiguration" Key -> DataSourceConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= DataSourceConfigurationProperty
dataSourceConfiguration]}
instance JSON.ToJSON QnAIntentConfigurationProperty where
  toJSON :: QnAIntentConfigurationProperty -> Value
toJSON QnAIntentConfigurationProperty {()
BedrockModelSpecificationProperty
DataSourceConfigurationProperty
haddock_workaround_ :: QnAIntentConfigurationProperty -> ()
bedrockModelConfiguration :: QnAIntentConfigurationProperty -> BedrockModelSpecificationProperty
dataSourceConfiguration :: QnAIntentConfigurationProperty -> DataSourceConfigurationProperty
haddock_workaround_ :: ()
bedrockModelConfiguration :: BedrockModelSpecificationProperty
dataSourceConfiguration :: DataSourceConfigurationProperty
..}
    = [(Key, Value)] -> Value
JSON.object
        [Key
"BedrockModelConfiguration" Key -> BedrockModelSpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= BedrockModelSpecificationProperty
bedrockModelConfiguration,
         Key
"DataSourceConfiguration" Key -> DataSourceConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= DataSourceConfigurationProperty
dataSourceConfiguration]
instance Property "BedrockModelConfiguration" QnAIntentConfigurationProperty where
  type PropertyType "BedrockModelConfiguration" QnAIntentConfigurationProperty = BedrockModelSpecificationProperty
  set :: PropertyType
  "BedrockModelConfiguration" QnAIntentConfigurationProperty
-> QnAIntentConfigurationProperty -> QnAIntentConfigurationProperty
set PropertyType
  "BedrockModelConfiguration" QnAIntentConfigurationProperty
newValue QnAIntentConfigurationProperty {()
BedrockModelSpecificationProperty
DataSourceConfigurationProperty
haddock_workaround_ :: QnAIntentConfigurationProperty -> ()
bedrockModelConfiguration :: QnAIntentConfigurationProperty -> BedrockModelSpecificationProperty
dataSourceConfiguration :: QnAIntentConfigurationProperty -> DataSourceConfigurationProperty
haddock_workaround_ :: ()
bedrockModelConfiguration :: BedrockModelSpecificationProperty
dataSourceConfiguration :: DataSourceConfigurationProperty
..}
    = QnAIntentConfigurationProperty
        {bedrockModelConfiguration :: BedrockModelSpecificationProperty
bedrockModelConfiguration = PropertyType
  "BedrockModelConfiguration" QnAIntentConfigurationProperty
BedrockModelSpecificationProperty
newValue, ()
DataSourceConfigurationProperty
haddock_workaround_ :: ()
dataSourceConfiguration :: DataSourceConfigurationProperty
haddock_workaround_ :: ()
dataSourceConfiguration :: DataSourceConfigurationProperty
..}
instance Property "DataSourceConfiguration" QnAIntentConfigurationProperty where
  type PropertyType "DataSourceConfiguration" QnAIntentConfigurationProperty = DataSourceConfigurationProperty
  set :: PropertyType
  "DataSourceConfiguration" QnAIntentConfigurationProperty
-> QnAIntentConfigurationProperty -> QnAIntentConfigurationProperty
set PropertyType
  "DataSourceConfiguration" QnAIntentConfigurationProperty
newValue QnAIntentConfigurationProperty {()
BedrockModelSpecificationProperty
DataSourceConfigurationProperty
haddock_workaround_ :: QnAIntentConfigurationProperty -> ()
bedrockModelConfiguration :: QnAIntentConfigurationProperty -> BedrockModelSpecificationProperty
dataSourceConfiguration :: QnAIntentConfigurationProperty -> DataSourceConfigurationProperty
haddock_workaround_ :: ()
bedrockModelConfiguration :: BedrockModelSpecificationProperty
dataSourceConfiguration :: DataSourceConfigurationProperty
..}
    = QnAIntentConfigurationProperty
        {dataSourceConfiguration :: DataSourceConfigurationProperty
dataSourceConfiguration = PropertyType
  "DataSourceConfiguration" QnAIntentConfigurationProperty
DataSourceConfigurationProperty
newValue, ()
BedrockModelSpecificationProperty
haddock_workaround_ :: ()
bedrockModelConfiguration :: BedrockModelSpecificationProperty
haddock_workaround_ :: ()
bedrockModelConfiguration :: BedrockModelSpecificationProperty
..}