module Stratosphere.Kendra.DataSource.SalesforceKnowledgeArticleConfigurationProperty (
        module Exports,
        SalesforceKnowledgeArticleConfigurationProperty(..),
        mkSalesforceKnowledgeArticleConfigurationProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Kendra.DataSource.SalesforceCustomKnowledgeArticleTypeConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.Kendra.DataSource.SalesforceStandardKnowledgeArticleTypeConfigurationProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data SalesforceKnowledgeArticleConfigurationProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kendra-datasource-salesforceknowledgearticleconfiguration.html>
    SalesforceKnowledgeArticleConfigurationProperty {SalesforceKnowledgeArticleConfigurationProperty -> ()
haddock_workaround_ :: (),
                                                     -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kendra-datasource-salesforceknowledgearticleconfiguration.html#cfn-kendra-datasource-salesforceknowledgearticleconfiguration-customknowledgearticletypeconfigurations>
                                                     SalesforceKnowledgeArticleConfigurationProperty
-> Maybe
     [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
customKnowledgeArticleTypeConfigurations :: (Prelude.Maybe [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]),
                                                     -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kendra-datasource-salesforceknowledgearticleconfiguration.html#cfn-kendra-datasource-salesforceknowledgearticleconfiguration-includedstates>
                                                     SalesforceKnowledgeArticleConfigurationProperty -> ValueList Text
includedStates :: (ValueList Prelude.Text),
                                                     -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-kendra-datasource-salesforceknowledgearticleconfiguration.html#cfn-kendra-datasource-salesforceknowledgearticleconfiguration-standardknowledgearticletypeconfiguration>
                                                     SalesforceKnowledgeArticleConfigurationProperty
-> Maybe
     SalesforceStandardKnowledgeArticleTypeConfigurationProperty
standardKnowledgeArticleTypeConfiguration :: (Prelude.Maybe SalesforceStandardKnowledgeArticleTypeConfigurationProperty)}
  deriving stock (SalesforceKnowledgeArticleConfigurationProperty
-> SalesforceKnowledgeArticleConfigurationProperty -> Bool
(SalesforceKnowledgeArticleConfigurationProperty
 -> SalesforceKnowledgeArticleConfigurationProperty -> Bool)
-> (SalesforceKnowledgeArticleConfigurationProperty
    -> SalesforceKnowledgeArticleConfigurationProperty -> Bool)
-> Eq SalesforceKnowledgeArticleConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SalesforceKnowledgeArticleConfigurationProperty
-> SalesforceKnowledgeArticleConfigurationProperty -> Bool
== :: SalesforceKnowledgeArticleConfigurationProperty
-> SalesforceKnowledgeArticleConfigurationProperty -> Bool
$c/= :: SalesforceKnowledgeArticleConfigurationProperty
-> SalesforceKnowledgeArticleConfigurationProperty -> Bool
/= :: SalesforceKnowledgeArticleConfigurationProperty
-> SalesforceKnowledgeArticleConfigurationProperty -> Bool
Prelude.Eq, Int -> SalesforceKnowledgeArticleConfigurationProperty -> ShowS
[SalesforceKnowledgeArticleConfigurationProperty] -> ShowS
SalesforceKnowledgeArticleConfigurationProperty -> String
(Int -> SalesforceKnowledgeArticleConfigurationProperty -> ShowS)
-> (SalesforceKnowledgeArticleConfigurationProperty -> String)
-> ([SalesforceKnowledgeArticleConfigurationProperty] -> ShowS)
-> Show SalesforceKnowledgeArticleConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SalesforceKnowledgeArticleConfigurationProperty -> ShowS
showsPrec :: Int -> SalesforceKnowledgeArticleConfigurationProperty -> ShowS
$cshow :: SalesforceKnowledgeArticleConfigurationProperty -> String
show :: SalesforceKnowledgeArticleConfigurationProperty -> String
$cshowList :: [SalesforceKnowledgeArticleConfigurationProperty] -> ShowS
showList :: [SalesforceKnowledgeArticleConfigurationProperty] -> ShowS
Prelude.Show)
mkSalesforceKnowledgeArticleConfigurationProperty ::
  ValueList Prelude.Text
  -> SalesforceKnowledgeArticleConfigurationProperty
mkSalesforceKnowledgeArticleConfigurationProperty :: ValueList Text -> SalesforceKnowledgeArticleConfigurationProperty
mkSalesforceKnowledgeArticleConfigurationProperty ValueList Text
includedStates
  = SalesforceKnowledgeArticleConfigurationProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), includedStates :: ValueList Text
includedStates = ValueList Text
includedStates,
       customKnowledgeArticleTypeConfigurations :: Maybe [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
customKnowledgeArticleTypeConfigurations = Maybe [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
forall a. Maybe a
Prelude.Nothing,
       standardKnowledgeArticleTypeConfiguration :: Maybe SalesforceStandardKnowledgeArticleTypeConfigurationProperty
standardKnowledgeArticleTypeConfiguration = Maybe SalesforceStandardKnowledgeArticleTypeConfigurationProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties SalesforceKnowledgeArticleConfigurationProperty where
  toResourceProperties :: SalesforceKnowledgeArticleConfigurationProperty
-> ResourceProperties
toResourceProperties
    SalesforceKnowledgeArticleConfigurationProperty {Maybe [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
Maybe SalesforceStandardKnowledgeArticleTypeConfigurationProperty
()
ValueList Text
haddock_workaround_ :: SalesforceKnowledgeArticleConfigurationProperty -> ()
customKnowledgeArticleTypeConfigurations :: SalesforceKnowledgeArticleConfigurationProperty
-> Maybe
     [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
includedStates :: SalesforceKnowledgeArticleConfigurationProperty -> ValueList Text
standardKnowledgeArticleTypeConfiguration :: SalesforceKnowledgeArticleConfigurationProperty
-> Maybe
     SalesforceStandardKnowledgeArticleTypeConfigurationProperty
haddock_workaround_ :: ()
customKnowledgeArticleTypeConfigurations :: Maybe [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
includedStates :: ValueList Text
standardKnowledgeArticleTypeConfiguration :: Maybe SalesforceStandardKnowledgeArticleTypeConfigurationProperty
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::Kendra::DataSource.SalesforceKnowledgeArticleConfiguration",
         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
"IncludedStates" 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
includedStates]
                           ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                              [Key
-> [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
-> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CustomKnowledgeArticleTypeConfigurations"
                                 ([SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
 -> (Key, Value))
-> Maybe
     [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
customKnowledgeArticleTypeConfigurations,
                               Key
-> SalesforceStandardKnowledgeArticleTypeConfigurationProperty
-> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"StandardKnowledgeArticleTypeConfiguration"
                                 (SalesforceStandardKnowledgeArticleTypeConfigurationProperty
 -> (Key, Value))
-> Maybe
     SalesforceStandardKnowledgeArticleTypeConfigurationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SalesforceStandardKnowledgeArticleTypeConfigurationProperty
standardKnowledgeArticleTypeConfiguration]))}
instance JSON.ToJSON SalesforceKnowledgeArticleConfigurationProperty where
  toJSON :: SalesforceKnowledgeArticleConfigurationProperty -> Value
toJSON SalesforceKnowledgeArticleConfigurationProperty {Maybe [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
Maybe SalesforceStandardKnowledgeArticleTypeConfigurationProperty
()
ValueList Text
haddock_workaround_ :: SalesforceKnowledgeArticleConfigurationProperty -> ()
customKnowledgeArticleTypeConfigurations :: SalesforceKnowledgeArticleConfigurationProperty
-> Maybe
     [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
includedStates :: SalesforceKnowledgeArticleConfigurationProperty -> ValueList Text
standardKnowledgeArticleTypeConfiguration :: SalesforceKnowledgeArticleConfigurationProperty
-> Maybe
     SalesforceStandardKnowledgeArticleTypeConfigurationProperty
haddock_workaround_ :: ()
customKnowledgeArticleTypeConfigurations :: Maybe [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
includedStates :: ValueList Text
standardKnowledgeArticleTypeConfiguration :: Maybe SalesforceStandardKnowledgeArticleTypeConfigurationProperty
..}
    = [(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
"IncludedStates" 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
includedStates]
              ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                 [Key
-> [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
-> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CustomKnowledgeArticleTypeConfigurations"
                    ([SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
 -> (Key, Value))
-> Maybe
     [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
customKnowledgeArticleTypeConfigurations,
                  Key
-> SalesforceStandardKnowledgeArticleTypeConfigurationProperty
-> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"StandardKnowledgeArticleTypeConfiguration"
                    (SalesforceStandardKnowledgeArticleTypeConfigurationProperty
 -> (Key, Value))
-> Maybe
     SalesforceStandardKnowledgeArticleTypeConfigurationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SalesforceStandardKnowledgeArticleTypeConfigurationProperty
standardKnowledgeArticleTypeConfiguration])))
instance Property "CustomKnowledgeArticleTypeConfigurations" SalesforceKnowledgeArticleConfigurationProperty where
  type PropertyType "CustomKnowledgeArticleTypeConfigurations" SalesforceKnowledgeArticleConfigurationProperty = [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
  set :: PropertyType
  "CustomKnowledgeArticleTypeConfigurations"
  SalesforceKnowledgeArticleConfigurationProperty
-> SalesforceKnowledgeArticleConfigurationProperty
-> SalesforceKnowledgeArticleConfigurationProperty
set PropertyType
  "CustomKnowledgeArticleTypeConfigurations"
  SalesforceKnowledgeArticleConfigurationProperty
newValue SalesforceKnowledgeArticleConfigurationProperty {Maybe [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
Maybe SalesforceStandardKnowledgeArticleTypeConfigurationProperty
()
ValueList Text
haddock_workaround_ :: SalesforceKnowledgeArticleConfigurationProperty -> ()
customKnowledgeArticleTypeConfigurations :: SalesforceKnowledgeArticleConfigurationProperty
-> Maybe
     [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
includedStates :: SalesforceKnowledgeArticleConfigurationProperty -> ValueList Text
standardKnowledgeArticleTypeConfiguration :: SalesforceKnowledgeArticleConfigurationProperty
-> Maybe
     SalesforceStandardKnowledgeArticleTypeConfigurationProperty
haddock_workaround_ :: ()
customKnowledgeArticleTypeConfigurations :: Maybe [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
includedStates :: ValueList Text
standardKnowledgeArticleTypeConfiguration :: Maybe SalesforceStandardKnowledgeArticleTypeConfigurationProperty
..}
    = SalesforceKnowledgeArticleConfigurationProperty
        {customKnowledgeArticleTypeConfigurations :: Maybe [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
customKnowledgeArticleTypeConfigurations = [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
-> Maybe
     [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
PropertyType
  "CustomKnowledgeArticleTypeConfigurations"
  SalesforceKnowledgeArticleConfigurationProperty
newValue,
         Maybe SalesforceStandardKnowledgeArticleTypeConfigurationProperty
()
ValueList Text
haddock_workaround_ :: ()
includedStates :: ValueList Text
standardKnowledgeArticleTypeConfiguration :: Maybe SalesforceStandardKnowledgeArticleTypeConfigurationProperty
haddock_workaround_ :: ()
includedStates :: ValueList Text
standardKnowledgeArticleTypeConfiguration :: Maybe SalesforceStandardKnowledgeArticleTypeConfigurationProperty
..}
instance Property "IncludedStates" SalesforceKnowledgeArticleConfigurationProperty where
  type PropertyType "IncludedStates" SalesforceKnowledgeArticleConfigurationProperty = ValueList Prelude.Text
  set :: PropertyType
  "IncludedStates" SalesforceKnowledgeArticleConfigurationProperty
-> SalesforceKnowledgeArticleConfigurationProperty
-> SalesforceKnowledgeArticleConfigurationProperty
set PropertyType
  "IncludedStates" SalesforceKnowledgeArticleConfigurationProperty
newValue SalesforceKnowledgeArticleConfigurationProperty {Maybe [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
Maybe SalesforceStandardKnowledgeArticleTypeConfigurationProperty
()
ValueList Text
haddock_workaround_ :: SalesforceKnowledgeArticleConfigurationProperty -> ()
customKnowledgeArticleTypeConfigurations :: SalesforceKnowledgeArticleConfigurationProperty
-> Maybe
     [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
includedStates :: SalesforceKnowledgeArticleConfigurationProperty -> ValueList Text
standardKnowledgeArticleTypeConfiguration :: SalesforceKnowledgeArticleConfigurationProperty
-> Maybe
     SalesforceStandardKnowledgeArticleTypeConfigurationProperty
haddock_workaround_ :: ()
customKnowledgeArticleTypeConfigurations :: Maybe [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
includedStates :: ValueList Text
standardKnowledgeArticleTypeConfiguration :: Maybe SalesforceStandardKnowledgeArticleTypeConfigurationProperty
..}
    = SalesforceKnowledgeArticleConfigurationProperty
        {includedStates :: ValueList Text
includedStates = PropertyType
  "IncludedStates" SalesforceKnowledgeArticleConfigurationProperty
ValueList Text
newValue, Maybe [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
Maybe SalesforceStandardKnowledgeArticleTypeConfigurationProperty
()
haddock_workaround_ :: ()
customKnowledgeArticleTypeConfigurations :: Maybe [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
standardKnowledgeArticleTypeConfiguration :: Maybe SalesforceStandardKnowledgeArticleTypeConfigurationProperty
haddock_workaround_ :: ()
customKnowledgeArticleTypeConfigurations :: Maybe [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
standardKnowledgeArticleTypeConfiguration :: Maybe SalesforceStandardKnowledgeArticleTypeConfigurationProperty
..}
instance Property "StandardKnowledgeArticleTypeConfiguration" SalesforceKnowledgeArticleConfigurationProperty where
  type PropertyType "StandardKnowledgeArticleTypeConfiguration" SalesforceKnowledgeArticleConfigurationProperty = SalesforceStandardKnowledgeArticleTypeConfigurationProperty
  set :: PropertyType
  "StandardKnowledgeArticleTypeConfiguration"
  SalesforceKnowledgeArticleConfigurationProperty
-> SalesforceKnowledgeArticleConfigurationProperty
-> SalesforceKnowledgeArticleConfigurationProperty
set PropertyType
  "StandardKnowledgeArticleTypeConfiguration"
  SalesforceKnowledgeArticleConfigurationProperty
newValue SalesforceKnowledgeArticleConfigurationProperty {Maybe [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
Maybe SalesforceStandardKnowledgeArticleTypeConfigurationProperty
()
ValueList Text
haddock_workaround_ :: SalesforceKnowledgeArticleConfigurationProperty -> ()
customKnowledgeArticleTypeConfigurations :: SalesforceKnowledgeArticleConfigurationProperty
-> Maybe
     [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
includedStates :: SalesforceKnowledgeArticleConfigurationProperty -> ValueList Text
standardKnowledgeArticleTypeConfiguration :: SalesforceKnowledgeArticleConfigurationProperty
-> Maybe
     SalesforceStandardKnowledgeArticleTypeConfigurationProperty
haddock_workaround_ :: ()
customKnowledgeArticleTypeConfigurations :: Maybe [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
includedStates :: ValueList Text
standardKnowledgeArticleTypeConfiguration :: Maybe SalesforceStandardKnowledgeArticleTypeConfigurationProperty
..}
    = SalesforceKnowledgeArticleConfigurationProperty
        {standardKnowledgeArticleTypeConfiguration :: Maybe SalesforceStandardKnowledgeArticleTypeConfigurationProperty
standardKnowledgeArticleTypeConfiguration = SalesforceStandardKnowledgeArticleTypeConfigurationProperty
-> Maybe
     SalesforceStandardKnowledgeArticleTypeConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "StandardKnowledgeArticleTypeConfiguration"
  SalesforceKnowledgeArticleConfigurationProperty
SalesforceStandardKnowledgeArticleTypeConfigurationProperty
newValue,
         Maybe [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
()
ValueList Text
haddock_workaround_ :: ()
customKnowledgeArticleTypeConfigurations :: Maybe [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
includedStates :: ValueList Text
haddock_workaround_ :: ()
customKnowledgeArticleTypeConfigurations :: Maybe [SalesforceCustomKnowledgeArticleTypeConfigurationProperty]
includedStates :: ValueList Text
..}