module Stratosphere.DataZone.DataSource.RedshiftCredentialConfigurationProperty (
        RedshiftCredentialConfigurationProperty(..),
        mkRedshiftCredentialConfigurationProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data RedshiftCredentialConfigurationProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-datazone-datasource-redshiftcredentialconfiguration.html>
    RedshiftCredentialConfigurationProperty {RedshiftCredentialConfigurationProperty -> ()
haddock_workaround_ :: (),
                                             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-datazone-datasource-redshiftcredentialconfiguration.html#cfn-datazone-datasource-redshiftcredentialconfiguration-secretmanagerarn>
                                             RedshiftCredentialConfigurationProperty -> Value Text
secretManagerArn :: (Value Prelude.Text)}
  deriving stock (RedshiftCredentialConfigurationProperty
-> RedshiftCredentialConfigurationProperty -> Bool
(RedshiftCredentialConfigurationProperty
 -> RedshiftCredentialConfigurationProperty -> Bool)
-> (RedshiftCredentialConfigurationProperty
    -> RedshiftCredentialConfigurationProperty -> Bool)
-> Eq RedshiftCredentialConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RedshiftCredentialConfigurationProperty
-> RedshiftCredentialConfigurationProperty -> Bool
== :: RedshiftCredentialConfigurationProperty
-> RedshiftCredentialConfigurationProperty -> Bool
$c/= :: RedshiftCredentialConfigurationProperty
-> RedshiftCredentialConfigurationProperty -> Bool
/= :: RedshiftCredentialConfigurationProperty
-> RedshiftCredentialConfigurationProperty -> Bool
Prelude.Eq, Int -> RedshiftCredentialConfigurationProperty -> ShowS
[RedshiftCredentialConfigurationProperty] -> ShowS
RedshiftCredentialConfigurationProperty -> String
(Int -> RedshiftCredentialConfigurationProperty -> ShowS)
-> (RedshiftCredentialConfigurationProperty -> String)
-> ([RedshiftCredentialConfigurationProperty] -> ShowS)
-> Show RedshiftCredentialConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RedshiftCredentialConfigurationProperty -> ShowS
showsPrec :: Int -> RedshiftCredentialConfigurationProperty -> ShowS
$cshow :: RedshiftCredentialConfigurationProperty -> String
show :: RedshiftCredentialConfigurationProperty -> String
$cshowList :: [RedshiftCredentialConfigurationProperty] -> ShowS
showList :: [RedshiftCredentialConfigurationProperty] -> ShowS
Prelude.Show)
mkRedshiftCredentialConfigurationProperty ::
  Value Prelude.Text -> RedshiftCredentialConfigurationProperty
mkRedshiftCredentialConfigurationProperty :: Value Text -> RedshiftCredentialConfigurationProperty
mkRedshiftCredentialConfigurationProperty Value Text
secretManagerArn
  = RedshiftCredentialConfigurationProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), secretManagerArn :: Value Text
secretManagerArn = Value Text
secretManagerArn}
instance ToResourceProperties RedshiftCredentialConfigurationProperty where
  toResourceProperties :: RedshiftCredentialConfigurationProperty -> ResourceProperties
toResourceProperties RedshiftCredentialConfigurationProperty {()
Value Text
haddock_workaround_ :: RedshiftCredentialConfigurationProperty -> ()
secretManagerArn :: RedshiftCredentialConfigurationProperty -> Value Text
haddock_workaround_ :: ()
secretManagerArn :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::DataZone::DataSource.RedshiftCredentialConfiguration",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"SecretManagerArn" 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
secretManagerArn]}
instance JSON.ToJSON RedshiftCredentialConfigurationProperty where
  toJSON :: RedshiftCredentialConfigurationProperty -> Value
toJSON RedshiftCredentialConfigurationProperty {()
Value Text
haddock_workaround_ :: RedshiftCredentialConfigurationProperty -> ()
secretManagerArn :: RedshiftCredentialConfigurationProperty -> Value Text
haddock_workaround_ :: ()
secretManagerArn :: Value Text
..}
    = [(Key, Value)] -> Value
JSON.object [Key
"SecretManagerArn" 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
secretManagerArn]
instance Property "SecretManagerArn" RedshiftCredentialConfigurationProperty where
  type PropertyType "SecretManagerArn" RedshiftCredentialConfigurationProperty = Value Prelude.Text
  set :: PropertyType
  "SecretManagerArn" RedshiftCredentialConfigurationProperty
-> RedshiftCredentialConfigurationProperty
-> RedshiftCredentialConfigurationProperty
set PropertyType
  "SecretManagerArn" RedshiftCredentialConfigurationProperty
newValue RedshiftCredentialConfigurationProperty {()
Value Text
haddock_workaround_ :: RedshiftCredentialConfigurationProperty -> ()
secretManagerArn :: RedshiftCredentialConfigurationProperty -> Value Text
haddock_workaround_ :: ()
secretManagerArn :: Value Text
..}
    = RedshiftCredentialConfigurationProperty
        {secretManagerArn :: Value Text
secretManagerArn = PropertyType
  "SecretManagerArn" RedshiftCredentialConfigurationProperty
Value Text
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}