module Stratosphere.Kendra.DataSource.WebCrawlerSiteMapsConfigurationProperty (
        WebCrawlerSiteMapsConfigurationProperty(..),
        mkWebCrawlerSiteMapsConfigurationProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data WebCrawlerSiteMapsConfigurationProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kendra-datasource-webcrawlersitemapsconfiguration.html>
    WebCrawlerSiteMapsConfigurationProperty {WebCrawlerSiteMapsConfigurationProperty -> ()
haddock_workaround_ :: (),
                                             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kendra-datasource-webcrawlersitemapsconfiguration.html#cfn-kendra-datasource-webcrawlersitemapsconfiguration-sitemaps>
                                             WebCrawlerSiteMapsConfigurationProperty -> ValueList Text
siteMaps :: (ValueList Prelude.Text)}
  deriving stock (WebCrawlerSiteMapsConfigurationProperty
-> WebCrawlerSiteMapsConfigurationProperty -> Bool
(WebCrawlerSiteMapsConfigurationProperty
 -> WebCrawlerSiteMapsConfigurationProperty -> Bool)
-> (WebCrawlerSiteMapsConfigurationProperty
    -> WebCrawlerSiteMapsConfigurationProperty -> Bool)
-> Eq WebCrawlerSiteMapsConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WebCrawlerSiteMapsConfigurationProperty
-> WebCrawlerSiteMapsConfigurationProperty -> Bool
== :: WebCrawlerSiteMapsConfigurationProperty
-> WebCrawlerSiteMapsConfigurationProperty -> Bool
$c/= :: WebCrawlerSiteMapsConfigurationProperty
-> WebCrawlerSiteMapsConfigurationProperty -> Bool
/= :: WebCrawlerSiteMapsConfigurationProperty
-> WebCrawlerSiteMapsConfigurationProperty -> Bool
Prelude.Eq, Int -> WebCrawlerSiteMapsConfigurationProperty -> ShowS
[WebCrawlerSiteMapsConfigurationProperty] -> ShowS
WebCrawlerSiteMapsConfigurationProperty -> String
(Int -> WebCrawlerSiteMapsConfigurationProperty -> ShowS)
-> (WebCrawlerSiteMapsConfigurationProperty -> String)
-> ([WebCrawlerSiteMapsConfigurationProperty] -> ShowS)
-> Show WebCrawlerSiteMapsConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> WebCrawlerSiteMapsConfigurationProperty -> ShowS
showsPrec :: Int -> WebCrawlerSiteMapsConfigurationProperty -> ShowS
$cshow :: WebCrawlerSiteMapsConfigurationProperty -> String
show :: WebCrawlerSiteMapsConfigurationProperty -> String
$cshowList :: [WebCrawlerSiteMapsConfigurationProperty] -> ShowS
showList :: [WebCrawlerSiteMapsConfigurationProperty] -> ShowS
Prelude.Show)
mkWebCrawlerSiteMapsConfigurationProperty ::
  ValueList Prelude.Text -> WebCrawlerSiteMapsConfigurationProperty
mkWebCrawlerSiteMapsConfigurationProperty :: ValueList Text -> WebCrawlerSiteMapsConfigurationProperty
mkWebCrawlerSiteMapsConfigurationProperty ValueList Text
siteMaps
  = WebCrawlerSiteMapsConfigurationProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), siteMaps :: ValueList Text
siteMaps = ValueList Text
siteMaps}
instance ToResourceProperties WebCrawlerSiteMapsConfigurationProperty where
  toResourceProperties :: WebCrawlerSiteMapsConfigurationProperty -> ResourceProperties
toResourceProperties WebCrawlerSiteMapsConfigurationProperty {()
ValueList Text
haddock_workaround_ :: WebCrawlerSiteMapsConfigurationProperty -> ()
siteMaps :: WebCrawlerSiteMapsConfigurationProperty -> ValueList Text
haddock_workaround_ :: ()
siteMaps :: ValueList Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::Kendra::DataSource.WebCrawlerSiteMapsConfiguration",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"SiteMaps" Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= ValueList Text
siteMaps]}
instance JSON.ToJSON WebCrawlerSiteMapsConfigurationProperty where
  toJSON :: WebCrawlerSiteMapsConfigurationProperty -> Value
toJSON WebCrawlerSiteMapsConfigurationProperty {()
ValueList Text
haddock_workaround_ :: WebCrawlerSiteMapsConfigurationProperty -> ()
siteMaps :: WebCrawlerSiteMapsConfigurationProperty -> ValueList Text
haddock_workaround_ :: ()
siteMaps :: ValueList Text
..}
    = [(Key, Value)] -> Value
JSON.object [Key
"SiteMaps" Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= ValueList Text
siteMaps]
instance Property "SiteMaps" WebCrawlerSiteMapsConfigurationProperty where
  type PropertyType "SiteMaps" WebCrawlerSiteMapsConfigurationProperty = ValueList Prelude.Text
  set :: PropertyType "SiteMaps" WebCrawlerSiteMapsConfigurationProperty
-> WebCrawlerSiteMapsConfigurationProperty
-> WebCrawlerSiteMapsConfigurationProperty
set PropertyType "SiteMaps" WebCrawlerSiteMapsConfigurationProperty
newValue WebCrawlerSiteMapsConfigurationProperty {()
ValueList Text
haddock_workaround_ :: WebCrawlerSiteMapsConfigurationProperty -> ()
siteMaps :: WebCrawlerSiteMapsConfigurationProperty -> ValueList Text
haddock_workaround_ :: ()
siteMaps :: ValueList Text
..}
    = WebCrawlerSiteMapsConfigurationProperty {siteMaps :: ValueList Text
siteMaps = PropertyType "SiteMaps" WebCrawlerSiteMapsConfigurationProperty
ValueList Text
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}