module Stratosphere.Athena.WorkGroup.WorkGroupConfigurationProperty (
        module Exports, WorkGroupConfigurationProperty(..),
        mkWorkGroupConfigurationProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Athena.WorkGroup.CustomerContentEncryptionConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.Athena.WorkGroup.EngineVersionProperty as Exports
import {-# SOURCE #-} Stratosphere.Athena.WorkGroup.ManagedQueryResultsConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.Athena.WorkGroup.ResultConfigurationProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data WorkGroupConfigurationProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-athena-workgroup-workgroupconfiguration.html>
    WorkGroupConfigurationProperty {WorkGroupConfigurationProperty -> ()
haddock_workaround_ :: (),
                                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-athena-workgroup-workgroupconfiguration.html#cfn-athena-workgroup-workgroupconfiguration-additionalconfiguration>
                                    WorkGroupConfigurationProperty -> Maybe (Value Text)
additionalConfiguration :: (Prelude.Maybe (Value Prelude.Text)),
                                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-athena-workgroup-workgroupconfiguration.html#cfn-athena-workgroup-workgroupconfiguration-bytesscannedcutoffperquery>
                                    WorkGroupConfigurationProperty -> Maybe (Value Integer)
bytesScannedCutoffPerQuery :: (Prelude.Maybe (Value Prelude.Integer)),
                                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-athena-workgroup-workgroupconfiguration.html#cfn-athena-workgroup-workgroupconfiguration-customercontentencryptionconfiguration>
                                    WorkGroupConfigurationProperty
-> Maybe CustomerContentEncryptionConfigurationProperty
customerContentEncryptionConfiguration :: (Prelude.Maybe CustomerContentEncryptionConfigurationProperty),
                                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-athena-workgroup-workgroupconfiguration.html#cfn-athena-workgroup-workgroupconfiguration-enforceworkgroupconfiguration>
                                    WorkGroupConfigurationProperty -> Maybe (Value Bool)
enforceWorkGroupConfiguration :: (Prelude.Maybe (Value Prelude.Bool)),
                                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-athena-workgroup-workgroupconfiguration.html#cfn-athena-workgroup-workgroupconfiguration-engineversion>
                                    WorkGroupConfigurationProperty -> Maybe EngineVersionProperty
engineVersion :: (Prelude.Maybe EngineVersionProperty),
                                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-athena-workgroup-workgroupconfiguration.html#cfn-athena-workgroup-workgroupconfiguration-executionrole>
                                    WorkGroupConfigurationProperty -> Maybe (Value Text)
executionRole :: (Prelude.Maybe (Value Prelude.Text)),
                                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-athena-workgroup-workgroupconfiguration.html#cfn-athena-workgroup-workgroupconfiguration-managedqueryresultsconfiguration>
                                    WorkGroupConfigurationProperty
-> Maybe ManagedQueryResultsConfigurationProperty
managedQueryResultsConfiguration :: (Prelude.Maybe ManagedQueryResultsConfigurationProperty),
                                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-athena-workgroup-workgroupconfiguration.html#cfn-athena-workgroup-workgroupconfiguration-publishcloudwatchmetricsenabled>
                                    WorkGroupConfigurationProperty -> Maybe (Value Bool)
publishCloudWatchMetricsEnabled :: (Prelude.Maybe (Value Prelude.Bool)),
                                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-athena-workgroup-workgroupconfiguration.html#cfn-athena-workgroup-workgroupconfiguration-requesterpaysenabled>
                                    WorkGroupConfigurationProperty -> Maybe (Value Bool)
requesterPaysEnabled :: (Prelude.Maybe (Value Prelude.Bool)),
                                    -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-athena-workgroup-workgroupconfiguration.html#cfn-athena-workgroup-workgroupconfiguration-resultconfiguration>
                                    WorkGroupConfigurationProperty -> Maybe ResultConfigurationProperty
resultConfiguration :: (Prelude.Maybe ResultConfigurationProperty)}
  deriving stock (WorkGroupConfigurationProperty
-> WorkGroupConfigurationProperty -> Bool
(WorkGroupConfigurationProperty
 -> WorkGroupConfigurationProperty -> Bool)
-> (WorkGroupConfigurationProperty
    -> WorkGroupConfigurationProperty -> Bool)
-> Eq WorkGroupConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WorkGroupConfigurationProperty
-> WorkGroupConfigurationProperty -> Bool
== :: WorkGroupConfigurationProperty
-> WorkGroupConfigurationProperty -> Bool
$c/= :: WorkGroupConfigurationProperty
-> WorkGroupConfigurationProperty -> Bool
/= :: WorkGroupConfigurationProperty
-> WorkGroupConfigurationProperty -> Bool
Prelude.Eq, Int -> WorkGroupConfigurationProperty -> ShowS
[WorkGroupConfigurationProperty] -> ShowS
WorkGroupConfigurationProperty -> String
(Int -> WorkGroupConfigurationProperty -> ShowS)
-> (WorkGroupConfigurationProperty -> String)
-> ([WorkGroupConfigurationProperty] -> ShowS)
-> Show WorkGroupConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> WorkGroupConfigurationProperty -> ShowS
showsPrec :: Int -> WorkGroupConfigurationProperty -> ShowS
$cshow :: WorkGroupConfigurationProperty -> String
show :: WorkGroupConfigurationProperty -> String
$cshowList :: [WorkGroupConfigurationProperty] -> ShowS
showList :: [WorkGroupConfigurationProperty] -> ShowS
Prelude.Show)
mkWorkGroupConfigurationProperty :: WorkGroupConfigurationProperty
mkWorkGroupConfigurationProperty :: WorkGroupConfigurationProperty
mkWorkGroupConfigurationProperty
  = WorkGroupConfigurationProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (),
       additionalConfiguration :: Maybe (Value Text)
additionalConfiguration = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       bytesScannedCutoffPerQuery :: Maybe (Value Integer)
bytesScannedCutoffPerQuery = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing,
       customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
customerContentEncryptionConfiguration = Maybe CustomerContentEncryptionConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
       enforceWorkGroupConfiguration :: Maybe (Value Bool)
enforceWorkGroupConfiguration = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
       engineVersion :: Maybe EngineVersionProperty
engineVersion = Maybe EngineVersionProperty
forall a. Maybe a
Prelude.Nothing, executionRole :: Maybe (Value Text)
executionRole = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
managedQueryResultsConfiguration = Maybe ManagedQueryResultsConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
       publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
publishCloudWatchMetricsEnabled = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
       requesterPaysEnabled :: Maybe (Value Bool)
requesterPaysEnabled = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
       resultConfiguration :: Maybe ResultConfigurationProperty
resultConfiguration = Maybe ResultConfigurationProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties WorkGroupConfigurationProperty where
  toResourceProperties :: WorkGroupConfigurationProperty -> ResourceProperties
toResourceProperties WorkGroupConfigurationProperty {Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CustomerContentEncryptionConfigurationProperty
Maybe EngineVersionProperty
Maybe ManagedQueryResultsConfigurationProperty
Maybe ResultConfigurationProperty
()
haddock_workaround_ :: WorkGroupConfigurationProperty -> ()
additionalConfiguration :: WorkGroupConfigurationProperty -> Maybe (Value Text)
bytesScannedCutoffPerQuery :: WorkGroupConfigurationProperty -> Maybe (Value Integer)
customerContentEncryptionConfiguration :: WorkGroupConfigurationProperty
-> Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
engineVersion :: WorkGroupConfigurationProperty -> Maybe EngineVersionProperty
executionRole :: WorkGroupConfigurationProperty -> Maybe (Value Text)
managedQueryResultsConfiguration :: WorkGroupConfigurationProperty
-> Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
requesterPaysEnabled :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
resultConfiguration :: WorkGroupConfigurationProperty -> Maybe ResultConfigurationProperty
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::Athena::WorkGroup.WorkGroupConfiguration",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
                        ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                           [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..=) Key
"AdditionalConfiguration"
                              (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
additionalConfiguration,
                            Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"BytesScannedCutoffPerQuery"
                              (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
bytesScannedCutoffPerQuery,
                            Key
-> CustomerContentEncryptionConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CustomerContentEncryptionConfiguration"
                              (CustomerContentEncryptionConfigurationProperty -> (Key, Value))
-> Maybe CustomerContentEncryptionConfigurationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CustomerContentEncryptionConfigurationProperty
customerContentEncryptionConfiguration,
                            Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EnforceWorkGroupConfiguration"
                              (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
enforceWorkGroupConfiguration,
                            Key -> EngineVersionProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EngineVersion" (EngineVersionProperty -> (Key, Value))
-> Maybe EngineVersionProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EngineVersionProperty
engineVersion,
                            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..=) Key
"ExecutionRole" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
executionRole,
                            Key -> ManagedQueryResultsConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ManagedQueryResultsConfiguration"
                              (ManagedQueryResultsConfigurationProperty -> (Key, Value))
-> Maybe ManagedQueryResultsConfigurationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ManagedQueryResultsConfigurationProperty
managedQueryResultsConfiguration,
                            Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PublishCloudWatchMetricsEnabled"
                              (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
publishCloudWatchMetricsEnabled,
                            Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RequesterPaysEnabled" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
requesterPaysEnabled,
                            Key -> ResultConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ResultConfiguration" (ResultConfigurationProperty -> (Key, Value))
-> Maybe ResultConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ResultConfigurationProperty
resultConfiguration])}
instance JSON.ToJSON WorkGroupConfigurationProperty where
  toJSON :: WorkGroupConfigurationProperty -> Value
toJSON WorkGroupConfigurationProperty {Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CustomerContentEncryptionConfigurationProperty
Maybe EngineVersionProperty
Maybe ManagedQueryResultsConfigurationProperty
Maybe ResultConfigurationProperty
()
haddock_workaround_ :: WorkGroupConfigurationProperty -> ()
additionalConfiguration :: WorkGroupConfigurationProperty -> Maybe (Value Text)
bytesScannedCutoffPerQuery :: WorkGroupConfigurationProperty -> Maybe (Value Integer)
customerContentEncryptionConfiguration :: WorkGroupConfigurationProperty
-> Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
engineVersion :: WorkGroupConfigurationProperty -> Maybe EngineVersionProperty
executionRole :: WorkGroupConfigurationProperty -> Maybe (Value Text)
managedQueryResultsConfiguration :: WorkGroupConfigurationProperty
-> Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
requesterPaysEnabled :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
resultConfiguration :: WorkGroupConfigurationProperty -> Maybe ResultConfigurationProperty
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
..}
    = [(Key, Value)] -> Value
JSON.object
        ([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
           ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
              [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..=) Key
"AdditionalConfiguration"
                 (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
additionalConfiguration,
               Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"BytesScannedCutoffPerQuery"
                 (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
bytesScannedCutoffPerQuery,
               Key
-> CustomerContentEncryptionConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CustomerContentEncryptionConfiguration"
                 (CustomerContentEncryptionConfigurationProperty -> (Key, Value))
-> Maybe CustomerContentEncryptionConfigurationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CustomerContentEncryptionConfigurationProperty
customerContentEncryptionConfiguration,
               Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EnforceWorkGroupConfiguration"
                 (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
enforceWorkGroupConfiguration,
               Key -> EngineVersionProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EngineVersion" (EngineVersionProperty -> (Key, Value))
-> Maybe EngineVersionProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EngineVersionProperty
engineVersion,
               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..=) Key
"ExecutionRole" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
executionRole,
               Key -> ManagedQueryResultsConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ManagedQueryResultsConfiguration"
                 (ManagedQueryResultsConfigurationProperty -> (Key, Value))
-> Maybe ManagedQueryResultsConfigurationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ManagedQueryResultsConfigurationProperty
managedQueryResultsConfiguration,
               Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PublishCloudWatchMetricsEnabled"
                 (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
publishCloudWatchMetricsEnabled,
               Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RequesterPaysEnabled" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
requesterPaysEnabled,
               Key -> ResultConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ResultConfiguration" (ResultConfigurationProperty -> (Key, Value))
-> Maybe ResultConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ResultConfigurationProperty
resultConfiguration]))
instance Property "AdditionalConfiguration" WorkGroupConfigurationProperty where
  type PropertyType "AdditionalConfiguration" WorkGroupConfigurationProperty = Value Prelude.Text
  set :: PropertyType
  "AdditionalConfiguration" WorkGroupConfigurationProperty
-> WorkGroupConfigurationProperty -> WorkGroupConfigurationProperty
set PropertyType
  "AdditionalConfiguration" WorkGroupConfigurationProperty
newValue WorkGroupConfigurationProperty {Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CustomerContentEncryptionConfigurationProperty
Maybe EngineVersionProperty
Maybe ManagedQueryResultsConfigurationProperty
Maybe ResultConfigurationProperty
()
haddock_workaround_ :: WorkGroupConfigurationProperty -> ()
additionalConfiguration :: WorkGroupConfigurationProperty -> Maybe (Value Text)
bytesScannedCutoffPerQuery :: WorkGroupConfigurationProperty -> Maybe (Value Integer)
customerContentEncryptionConfiguration :: WorkGroupConfigurationProperty
-> Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
engineVersion :: WorkGroupConfigurationProperty -> Maybe EngineVersionProperty
executionRole :: WorkGroupConfigurationProperty -> Maybe (Value Text)
managedQueryResultsConfiguration :: WorkGroupConfigurationProperty
-> Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
requesterPaysEnabled :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
resultConfiguration :: WorkGroupConfigurationProperty -> Maybe ResultConfigurationProperty
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
..}
    = WorkGroupConfigurationProperty
        {additionalConfiguration :: Maybe (Value Text)
additionalConfiguration = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "AdditionalConfiguration" WorkGroupConfigurationProperty
Value Text
newValue, Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CustomerContentEncryptionConfigurationProperty
Maybe EngineVersionProperty
Maybe ManagedQueryResultsConfigurationProperty
Maybe ResultConfigurationProperty
()
haddock_workaround_ :: ()
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
haddock_workaround_ :: ()
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
..}
instance Property "BytesScannedCutoffPerQuery" WorkGroupConfigurationProperty where
  type PropertyType "BytesScannedCutoffPerQuery" WorkGroupConfigurationProperty = Value Prelude.Integer
  set :: PropertyType
  "BytesScannedCutoffPerQuery" WorkGroupConfigurationProperty
-> WorkGroupConfigurationProperty -> WorkGroupConfigurationProperty
set PropertyType
  "BytesScannedCutoffPerQuery" WorkGroupConfigurationProperty
newValue WorkGroupConfigurationProperty {Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CustomerContentEncryptionConfigurationProperty
Maybe EngineVersionProperty
Maybe ManagedQueryResultsConfigurationProperty
Maybe ResultConfigurationProperty
()
haddock_workaround_ :: WorkGroupConfigurationProperty -> ()
additionalConfiguration :: WorkGroupConfigurationProperty -> Maybe (Value Text)
bytesScannedCutoffPerQuery :: WorkGroupConfigurationProperty -> Maybe (Value Integer)
customerContentEncryptionConfiguration :: WorkGroupConfigurationProperty
-> Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
engineVersion :: WorkGroupConfigurationProperty -> Maybe EngineVersionProperty
executionRole :: WorkGroupConfigurationProperty -> Maybe (Value Text)
managedQueryResultsConfiguration :: WorkGroupConfigurationProperty
-> Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
requesterPaysEnabled :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
resultConfiguration :: WorkGroupConfigurationProperty -> Maybe ResultConfigurationProperty
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
..}
    = WorkGroupConfigurationProperty
        {bytesScannedCutoffPerQuery :: Maybe (Value Integer)
bytesScannedCutoffPerQuery = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "BytesScannedCutoffPerQuery" WorkGroupConfigurationProperty
Value Integer
newValue, Maybe (Value Bool)
Maybe (Value Text)
Maybe CustomerContentEncryptionConfigurationProperty
Maybe EngineVersionProperty
Maybe ManagedQueryResultsConfigurationProperty
Maybe ResultConfigurationProperty
()
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
..}
instance Property "CustomerContentEncryptionConfiguration" WorkGroupConfigurationProperty where
  type PropertyType "CustomerContentEncryptionConfiguration" WorkGroupConfigurationProperty = CustomerContentEncryptionConfigurationProperty
  set :: PropertyType
  "CustomerContentEncryptionConfiguration"
  WorkGroupConfigurationProperty
-> WorkGroupConfigurationProperty -> WorkGroupConfigurationProperty
set PropertyType
  "CustomerContentEncryptionConfiguration"
  WorkGroupConfigurationProperty
newValue WorkGroupConfigurationProperty {Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CustomerContentEncryptionConfigurationProperty
Maybe EngineVersionProperty
Maybe ManagedQueryResultsConfigurationProperty
Maybe ResultConfigurationProperty
()
haddock_workaround_ :: WorkGroupConfigurationProperty -> ()
additionalConfiguration :: WorkGroupConfigurationProperty -> Maybe (Value Text)
bytesScannedCutoffPerQuery :: WorkGroupConfigurationProperty -> Maybe (Value Integer)
customerContentEncryptionConfiguration :: WorkGroupConfigurationProperty
-> Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
engineVersion :: WorkGroupConfigurationProperty -> Maybe EngineVersionProperty
executionRole :: WorkGroupConfigurationProperty -> Maybe (Value Text)
managedQueryResultsConfiguration :: WorkGroupConfigurationProperty
-> Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
requesterPaysEnabled :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
resultConfiguration :: WorkGroupConfigurationProperty -> Maybe ResultConfigurationProperty
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
..}
    = WorkGroupConfigurationProperty
        {customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
customerContentEncryptionConfiguration = CustomerContentEncryptionConfigurationProperty
-> Maybe CustomerContentEncryptionConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "CustomerContentEncryptionConfiguration"
  WorkGroupConfigurationProperty
CustomerContentEncryptionConfigurationProperty
newValue,
         Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe EngineVersionProperty
Maybe ManagedQueryResultsConfigurationProperty
Maybe ResultConfigurationProperty
()
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
..}
instance Property "EnforceWorkGroupConfiguration" WorkGroupConfigurationProperty where
  type PropertyType "EnforceWorkGroupConfiguration" WorkGroupConfigurationProperty = Value Prelude.Bool
  set :: PropertyType
  "EnforceWorkGroupConfiguration" WorkGroupConfigurationProperty
-> WorkGroupConfigurationProperty -> WorkGroupConfigurationProperty
set PropertyType
  "EnforceWorkGroupConfiguration" WorkGroupConfigurationProperty
newValue WorkGroupConfigurationProperty {Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CustomerContentEncryptionConfigurationProperty
Maybe EngineVersionProperty
Maybe ManagedQueryResultsConfigurationProperty
Maybe ResultConfigurationProperty
()
haddock_workaround_ :: WorkGroupConfigurationProperty -> ()
additionalConfiguration :: WorkGroupConfigurationProperty -> Maybe (Value Text)
bytesScannedCutoffPerQuery :: WorkGroupConfigurationProperty -> Maybe (Value Integer)
customerContentEncryptionConfiguration :: WorkGroupConfigurationProperty
-> Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
engineVersion :: WorkGroupConfigurationProperty -> Maybe EngineVersionProperty
executionRole :: WorkGroupConfigurationProperty -> Maybe (Value Text)
managedQueryResultsConfiguration :: WorkGroupConfigurationProperty
-> Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
requesterPaysEnabled :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
resultConfiguration :: WorkGroupConfigurationProperty -> Maybe ResultConfigurationProperty
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
..}
    = WorkGroupConfigurationProperty
        {enforceWorkGroupConfiguration :: Maybe (Value Bool)
enforceWorkGroupConfiguration = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "EnforceWorkGroupConfiguration" WorkGroupConfigurationProperty
Value Bool
newValue, Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CustomerContentEncryptionConfigurationProperty
Maybe EngineVersionProperty
Maybe ManagedQueryResultsConfigurationProperty
Maybe ResultConfigurationProperty
()
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
..}
instance Property "EngineVersion" WorkGroupConfigurationProperty where
  type PropertyType "EngineVersion" WorkGroupConfigurationProperty = EngineVersionProperty
  set :: PropertyType "EngineVersion" WorkGroupConfigurationProperty
-> WorkGroupConfigurationProperty -> WorkGroupConfigurationProperty
set PropertyType "EngineVersion" WorkGroupConfigurationProperty
newValue WorkGroupConfigurationProperty {Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CustomerContentEncryptionConfigurationProperty
Maybe EngineVersionProperty
Maybe ManagedQueryResultsConfigurationProperty
Maybe ResultConfigurationProperty
()
haddock_workaround_ :: WorkGroupConfigurationProperty -> ()
additionalConfiguration :: WorkGroupConfigurationProperty -> Maybe (Value Text)
bytesScannedCutoffPerQuery :: WorkGroupConfigurationProperty -> Maybe (Value Integer)
customerContentEncryptionConfiguration :: WorkGroupConfigurationProperty
-> Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
engineVersion :: WorkGroupConfigurationProperty -> Maybe EngineVersionProperty
executionRole :: WorkGroupConfigurationProperty -> Maybe (Value Text)
managedQueryResultsConfiguration :: WorkGroupConfigurationProperty
-> Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
requesterPaysEnabled :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
resultConfiguration :: WorkGroupConfigurationProperty -> Maybe ResultConfigurationProperty
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
..}
    = WorkGroupConfigurationProperty
        {engineVersion :: Maybe EngineVersionProperty
engineVersion = EngineVersionProperty -> Maybe EngineVersionProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "EngineVersion" WorkGroupConfigurationProperty
EngineVersionProperty
newValue, Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CustomerContentEncryptionConfigurationProperty
Maybe ManagedQueryResultsConfigurationProperty
Maybe ResultConfigurationProperty
()
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
..}
instance Property "ExecutionRole" WorkGroupConfigurationProperty where
  type PropertyType "ExecutionRole" WorkGroupConfigurationProperty = Value Prelude.Text
  set :: PropertyType "ExecutionRole" WorkGroupConfigurationProperty
-> WorkGroupConfigurationProperty -> WorkGroupConfigurationProperty
set PropertyType "ExecutionRole" WorkGroupConfigurationProperty
newValue WorkGroupConfigurationProperty {Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CustomerContentEncryptionConfigurationProperty
Maybe EngineVersionProperty
Maybe ManagedQueryResultsConfigurationProperty
Maybe ResultConfigurationProperty
()
haddock_workaround_ :: WorkGroupConfigurationProperty -> ()
additionalConfiguration :: WorkGroupConfigurationProperty -> Maybe (Value Text)
bytesScannedCutoffPerQuery :: WorkGroupConfigurationProperty -> Maybe (Value Integer)
customerContentEncryptionConfiguration :: WorkGroupConfigurationProperty
-> Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
engineVersion :: WorkGroupConfigurationProperty -> Maybe EngineVersionProperty
executionRole :: WorkGroupConfigurationProperty -> Maybe (Value Text)
managedQueryResultsConfiguration :: WorkGroupConfigurationProperty
-> Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
requesterPaysEnabled :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
resultConfiguration :: WorkGroupConfigurationProperty -> Maybe ResultConfigurationProperty
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
..}
    = WorkGroupConfigurationProperty
        {executionRole :: Maybe (Value Text)
executionRole = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ExecutionRole" WorkGroupConfigurationProperty
Value Text
newValue, Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CustomerContentEncryptionConfigurationProperty
Maybe EngineVersionProperty
Maybe ManagedQueryResultsConfigurationProperty
Maybe ResultConfigurationProperty
()
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
..}
instance Property "ManagedQueryResultsConfiguration" WorkGroupConfigurationProperty where
  type PropertyType "ManagedQueryResultsConfiguration" WorkGroupConfigurationProperty = ManagedQueryResultsConfigurationProperty
  set :: PropertyType
  "ManagedQueryResultsConfiguration" WorkGroupConfigurationProperty
-> WorkGroupConfigurationProperty -> WorkGroupConfigurationProperty
set PropertyType
  "ManagedQueryResultsConfiguration" WorkGroupConfigurationProperty
newValue WorkGroupConfigurationProperty {Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CustomerContentEncryptionConfigurationProperty
Maybe EngineVersionProperty
Maybe ManagedQueryResultsConfigurationProperty
Maybe ResultConfigurationProperty
()
haddock_workaround_ :: WorkGroupConfigurationProperty -> ()
additionalConfiguration :: WorkGroupConfigurationProperty -> Maybe (Value Text)
bytesScannedCutoffPerQuery :: WorkGroupConfigurationProperty -> Maybe (Value Integer)
customerContentEncryptionConfiguration :: WorkGroupConfigurationProperty
-> Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
engineVersion :: WorkGroupConfigurationProperty -> Maybe EngineVersionProperty
executionRole :: WorkGroupConfigurationProperty -> Maybe (Value Text)
managedQueryResultsConfiguration :: WorkGroupConfigurationProperty
-> Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
requesterPaysEnabled :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
resultConfiguration :: WorkGroupConfigurationProperty -> Maybe ResultConfigurationProperty
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
..}
    = WorkGroupConfigurationProperty
        {managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
managedQueryResultsConfiguration = ManagedQueryResultsConfigurationProperty
-> Maybe ManagedQueryResultsConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "ManagedQueryResultsConfiguration" WorkGroupConfigurationProperty
ManagedQueryResultsConfigurationProperty
newValue, Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CustomerContentEncryptionConfigurationProperty
Maybe EngineVersionProperty
Maybe ResultConfigurationProperty
()
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
..}
instance Property "PublishCloudWatchMetricsEnabled" WorkGroupConfigurationProperty where
  type PropertyType "PublishCloudWatchMetricsEnabled" WorkGroupConfigurationProperty = Value Prelude.Bool
  set :: PropertyType
  "PublishCloudWatchMetricsEnabled" WorkGroupConfigurationProperty
-> WorkGroupConfigurationProperty -> WorkGroupConfigurationProperty
set PropertyType
  "PublishCloudWatchMetricsEnabled" WorkGroupConfigurationProperty
newValue WorkGroupConfigurationProperty {Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CustomerContentEncryptionConfigurationProperty
Maybe EngineVersionProperty
Maybe ManagedQueryResultsConfigurationProperty
Maybe ResultConfigurationProperty
()
haddock_workaround_ :: WorkGroupConfigurationProperty -> ()
additionalConfiguration :: WorkGroupConfigurationProperty -> Maybe (Value Text)
bytesScannedCutoffPerQuery :: WorkGroupConfigurationProperty -> Maybe (Value Integer)
customerContentEncryptionConfiguration :: WorkGroupConfigurationProperty
-> Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
engineVersion :: WorkGroupConfigurationProperty -> Maybe EngineVersionProperty
executionRole :: WorkGroupConfigurationProperty -> Maybe (Value Text)
managedQueryResultsConfiguration :: WorkGroupConfigurationProperty
-> Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
requesterPaysEnabled :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
resultConfiguration :: WorkGroupConfigurationProperty -> Maybe ResultConfigurationProperty
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
..}
    = WorkGroupConfigurationProperty
        {publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
publishCloudWatchMetricsEnabled = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "PublishCloudWatchMetricsEnabled" WorkGroupConfigurationProperty
Value Bool
newValue, Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CustomerContentEncryptionConfigurationProperty
Maybe EngineVersionProperty
Maybe ManagedQueryResultsConfigurationProperty
Maybe ResultConfigurationProperty
()
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
..}
instance Property "RequesterPaysEnabled" WorkGroupConfigurationProperty where
  type PropertyType "RequesterPaysEnabled" WorkGroupConfigurationProperty = Value Prelude.Bool
  set :: PropertyType "RequesterPaysEnabled" WorkGroupConfigurationProperty
-> WorkGroupConfigurationProperty -> WorkGroupConfigurationProperty
set PropertyType "RequesterPaysEnabled" WorkGroupConfigurationProperty
newValue WorkGroupConfigurationProperty {Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CustomerContentEncryptionConfigurationProperty
Maybe EngineVersionProperty
Maybe ManagedQueryResultsConfigurationProperty
Maybe ResultConfigurationProperty
()
haddock_workaround_ :: WorkGroupConfigurationProperty -> ()
additionalConfiguration :: WorkGroupConfigurationProperty -> Maybe (Value Text)
bytesScannedCutoffPerQuery :: WorkGroupConfigurationProperty -> Maybe (Value Integer)
customerContentEncryptionConfiguration :: WorkGroupConfigurationProperty
-> Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
engineVersion :: WorkGroupConfigurationProperty -> Maybe EngineVersionProperty
executionRole :: WorkGroupConfigurationProperty -> Maybe (Value Text)
managedQueryResultsConfiguration :: WorkGroupConfigurationProperty
-> Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
requesterPaysEnabled :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
resultConfiguration :: WorkGroupConfigurationProperty -> Maybe ResultConfigurationProperty
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
..}
    = WorkGroupConfigurationProperty
        {requesterPaysEnabled :: Maybe (Value Bool)
requesterPaysEnabled = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "RequesterPaysEnabled" WorkGroupConfigurationProperty
Value Bool
newValue, Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CustomerContentEncryptionConfigurationProperty
Maybe EngineVersionProperty
Maybe ManagedQueryResultsConfigurationProperty
Maybe ResultConfigurationProperty
()
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
..}
instance Property "ResultConfiguration" WorkGroupConfigurationProperty where
  type PropertyType "ResultConfiguration" WorkGroupConfigurationProperty = ResultConfigurationProperty
  set :: PropertyType "ResultConfiguration" WorkGroupConfigurationProperty
-> WorkGroupConfigurationProperty -> WorkGroupConfigurationProperty
set PropertyType "ResultConfiguration" WorkGroupConfigurationProperty
newValue WorkGroupConfigurationProperty {Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CustomerContentEncryptionConfigurationProperty
Maybe EngineVersionProperty
Maybe ManagedQueryResultsConfigurationProperty
Maybe ResultConfigurationProperty
()
haddock_workaround_ :: WorkGroupConfigurationProperty -> ()
additionalConfiguration :: WorkGroupConfigurationProperty -> Maybe (Value Text)
bytesScannedCutoffPerQuery :: WorkGroupConfigurationProperty -> Maybe (Value Integer)
customerContentEncryptionConfiguration :: WorkGroupConfigurationProperty
-> Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
engineVersion :: WorkGroupConfigurationProperty -> Maybe EngineVersionProperty
executionRole :: WorkGroupConfigurationProperty -> Maybe (Value Text)
managedQueryResultsConfiguration :: WorkGroupConfigurationProperty
-> Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
requesterPaysEnabled :: WorkGroupConfigurationProperty -> Maybe (Value Bool)
resultConfiguration :: WorkGroupConfigurationProperty -> Maybe ResultConfigurationProperty
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
resultConfiguration :: Maybe ResultConfigurationProperty
..}
    = WorkGroupConfigurationProperty
        {resultConfiguration :: Maybe ResultConfigurationProperty
resultConfiguration = ResultConfigurationProperty -> Maybe ResultConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ResultConfiguration" WorkGroupConfigurationProperty
ResultConfigurationProperty
newValue, Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CustomerContentEncryptionConfigurationProperty
Maybe EngineVersionProperty
Maybe ManagedQueryResultsConfigurationProperty
()
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
haddock_workaround_ :: ()
additionalConfiguration :: Maybe (Value Text)
bytesScannedCutoffPerQuery :: Maybe (Value Integer)
customerContentEncryptionConfiguration :: Maybe CustomerContentEncryptionConfigurationProperty
enforceWorkGroupConfiguration :: Maybe (Value Bool)
engineVersion :: Maybe EngineVersionProperty
executionRole :: Maybe (Value Text)
managedQueryResultsConfiguration :: Maybe ManagedQueryResultsConfigurationProperty
publishCloudWatchMetricsEnabled :: Maybe (Value Bool)
requesterPaysEnabled :: Maybe (Value Bool)
..}