module Stratosphere.IoTSiteWise.Dataset.KendraSourceDetailProperty (
        KendraSourceDetailProperty(..), mkKendraSourceDetailProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data KendraSourceDetailProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-iotsitewise-dataset-kendrasourcedetail.html>
    KendraSourceDetailProperty {KendraSourceDetailProperty -> ()
haddock_workaround_ :: (),
                                -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-iotsitewise-dataset-kendrasourcedetail.html#cfn-iotsitewise-dataset-kendrasourcedetail-knowledgebasearn>
                                KendraSourceDetailProperty -> Value Text
knowledgeBaseArn :: (Value Prelude.Text),
                                -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-iotsitewise-dataset-kendrasourcedetail.html#cfn-iotsitewise-dataset-kendrasourcedetail-rolearn>
                                KendraSourceDetailProperty -> Value Text
roleArn :: (Value Prelude.Text)}
  deriving stock (KendraSourceDetailProperty -> KendraSourceDetailProperty -> Bool
(KendraSourceDetailProperty -> KendraSourceDetailProperty -> Bool)
-> (KendraSourceDetailProperty
    -> KendraSourceDetailProperty -> Bool)
-> Eq KendraSourceDetailProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: KendraSourceDetailProperty -> KendraSourceDetailProperty -> Bool
== :: KendraSourceDetailProperty -> KendraSourceDetailProperty -> Bool
$c/= :: KendraSourceDetailProperty -> KendraSourceDetailProperty -> Bool
/= :: KendraSourceDetailProperty -> KendraSourceDetailProperty -> Bool
Prelude.Eq, Int -> KendraSourceDetailProperty -> ShowS
[KendraSourceDetailProperty] -> ShowS
KendraSourceDetailProperty -> String
(Int -> KendraSourceDetailProperty -> ShowS)
-> (KendraSourceDetailProperty -> String)
-> ([KendraSourceDetailProperty] -> ShowS)
-> Show KendraSourceDetailProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> KendraSourceDetailProperty -> ShowS
showsPrec :: Int -> KendraSourceDetailProperty -> ShowS
$cshow :: KendraSourceDetailProperty -> String
show :: KendraSourceDetailProperty -> String
$cshowList :: [KendraSourceDetailProperty] -> ShowS
showList :: [KendraSourceDetailProperty] -> ShowS
Prelude.Show)
mkKendraSourceDetailProperty ::
  Value Prelude.Text
  -> Value Prelude.Text -> KendraSourceDetailProperty
mkKendraSourceDetailProperty :: Value Text -> Value Text -> KendraSourceDetailProperty
mkKendraSourceDetailProperty Value Text
knowledgeBaseArn Value Text
roleArn
  = KendraSourceDetailProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), knowledgeBaseArn :: Value Text
knowledgeBaseArn = Value Text
knowledgeBaseArn,
       roleArn :: Value Text
roleArn = Value Text
roleArn}
instance ToResourceProperties KendraSourceDetailProperty where
  toResourceProperties :: KendraSourceDetailProperty -> ResourceProperties
toResourceProperties KendraSourceDetailProperty {()
Value Text
haddock_workaround_ :: KendraSourceDetailProperty -> ()
knowledgeBaseArn :: KendraSourceDetailProperty -> Value Text
roleArn :: KendraSourceDetailProperty -> Value Text
haddock_workaround_ :: ()
knowledgeBaseArn :: Value Text
roleArn :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::IoTSiteWise::Dataset.KendraSourceDetail",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"KnowledgeBaseArn" 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
knowledgeBaseArn,
                       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 KendraSourceDetailProperty where
  toJSON :: KendraSourceDetailProperty -> Value
toJSON KendraSourceDetailProperty {()
Value Text
haddock_workaround_ :: KendraSourceDetailProperty -> ()
knowledgeBaseArn :: KendraSourceDetailProperty -> Value Text
roleArn :: KendraSourceDetailProperty -> Value Text
haddock_workaround_ :: ()
knowledgeBaseArn :: Value Text
roleArn :: Value Text
..}
    = [(Key, Value)] -> Value
JSON.object
        [Key
"KnowledgeBaseArn" 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
knowledgeBaseArn,
         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 "KnowledgeBaseArn" KendraSourceDetailProperty where
  type PropertyType "KnowledgeBaseArn" KendraSourceDetailProperty = Value Prelude.Text
  set :: PropertyType "KnowledgeBaseArn" KendraSourceDetailProperty
-> KendraSourceDetailProperty -> KendraSourceDetailProperty
set PropertyType "KnowledgeBaseArn" KendraSourceDetailProperty
newValue KendraSourceDetailProperty {()
Value Text
haddock_workaround_ :: KendraSourceDetailProperty -> ()
knowledgeBaseArn :: KendraSourceDetailProperty -> Value Text
roleArn :: KendraSourceDetailProperty -> Value Text
haddock_workaround_ :: ()
knowledgeBaseArn :: Value Text
roleArn :: Value Text
..}
    = KendraSourceDetailProperty {knowledgeBaseArn :: Value Text
knowledgeBaseArn = PropertyType "KnowledgeBaseArn" KendraSourceDetailProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
roleArn :: Value Text
haddock_workaround_ :: ()
roleArn :: Value Text
..}
instance Property "RoleArn" KendraSourceDetailProperty where
  type PropertyType "RoleArn" KendraSourceDetailProperty = Value Prelude.Text
  set :: PropertyType "RoleArn" KendraSourceDetailProperty
-> KendraSourceDetailProperty -> KendraSourceDetailProperty
set PropertyType "RoleArn" KendraSourceDetailProperty
newValue KendraSourceDetailProperty {()
Value Text
haddock_workaround_ :: KendraSourceDetailProperty -> ()
knowledgeBaseArn :: KendraSourceDetailProperty -> Value Text
roleArn :: KendraSourceDetailProperty -> Value Text
haddock_workaround_ :: ()
knowledgeBaseArn :: Value Text
roleArn :: Value Text
..}
    = KendraSourceDetailProperty {roleArn :: Value Text
roleArn = PropertyType "RoleArn" KendraSourceDetailProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
knowledgeBaseArn :: Value Text
haddock_workaround_ :: ()
knowledgeBaseArn :: Value Text
..}