module Stratosphere.Config.ConfigurationRecorder.RecordingGroupProperty (
        module Exports, RecordingGroupProperty(..),
        mkRecordingGroupProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Config.ConfigurationRecorder.ExclusionByResourceTypesProperty as Exports
import {-# SOURCE #-} Stratosphere.Config.ConfigurationRecorder.RecordingStrategyProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data RecordingGroupProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-config-configurationrecorder-recordinggroup.html>
    RecordingGroupProperty {RecordingGroupProperty -> ()
haddock_workaround_ :: (),
                            -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-config-configurationrecorder-recordinggroup.html#cfn-config-configurationrecorder-recordinggroup-allsupported>
                            RecordingGroupProperty -> Maybe (Value Bool)
allSupported :: (Prelude.Maybe (Value Prelude.Bool)),
                            -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-config-configurationrecorder-recordinggroup.html#cfn-config-configurationrecorder-recordinggroup-exclusionbyresourcetypes>
                            RecordingGroupProperty -> Maybe ExclusionByResourceTypesProperty
exclusionByResourceTypes :: (Prelude.Maybe ExclusionByResourceTypesProperty),
                            -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-config-configurationrecorder-recordinggroup.html#cfn-config-configurationrecorder-recordinggroup-includeglobalresourcetypes>
                            RecordingGroupProperty -> Maybe (Value Bool)
includeGlobalResourceTypes :: (Prelude.Maybe (Value Prelude.Bool)),
                            -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-config-configurationrecorder-recordinggroup.html#cfn-config-configurationrecorder-recordinggroup-recordingstrategy>
                            RecordingGroupProperty -> Maybe RecordingStrategyProperty
recordingStrategy :: (Prelude.Maybe RecordingStrategyProperty),
                            -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-config-configurationrecorder-recordinggroup.html#cfn-config-configurationrecorder-recordinggroup-resourcetypes>
                            RecordingGroupProperty -> Maybe (ValueList Text)
resourceTypes :: (Prelude.Maybe (ValueList Prelude.Text))}
  deriving stock (RecordingGroupProperty -> RecordingGroupProperty -> Bool
(RecordingGroupProperty -> RecordingGroupProperty -> Bool)
-> (RecordingGroupProperty -> RecordingGroupProperty -> Bool)
-> Eq RecordingGroupProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RecordingGroupProperty -> RecordingGroupProperty -> Bool
== :: RecordingGroupProperty -> RecordingGroupProperty -> Bool
$c/= :: RecordingGroupProperty -> RecordingGroupProperty -> Bool
/= :: RecordingGroupProperty -> RecordingGroupProperty -> Bool
Prelude.Eq, Int -> RecordingGroupProperty -> ShowS
[RecordingGroupProperty] -> ShowS
RecordingGroupProperty -> String
(Int -> RecordingGroupProperty -> ShowS)
-> (RecordingGroupProperty -> String)
-> ([RecordingGroupProperty] -> ShowS)
-> Show RecordingGroupProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RecordingGroupProperty -> ShowS
showsPrec :: Int -> RecordingGroupProperty -> ShowS
$cshow :: RecordingGroupProperty -> String
show :: RecordingGroupProperty -> String
$cshowList :: [RecordingGroupProperty] -> ShowS
showList :: [RecordingGroupProperty] -> ShowS
Prelude.Show)
mkRecordingGroupProperty :: RecordingGroupProperty
mkRecordingGroupProperty :: RecordingGroupProperty
mkRecordingGroupProperty
  = RecordingGroupProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), allSupported :: Maybe (Value Bool)
allSupported = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
       exclusionByResourceTypes :: Maybe ExclusionByResourceTypesProperty
exclusionByResourceTypes = Maybe ExclusionByResourceTypesProperty
forall a. Maybe a
Prelude.Nothing,
       includeGlobalResourceTypes :: Maybe (Value Bool)
includeGlobalResourceTypes = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
       recordingStrategy :: Maybe RecordingStrategyProperty
recordingStrategy = Maybe RecordingStrategyProperty
forall a. Maybe a
Prelude.Nothing,
       resourceTypes :: Maybe (ValueList Text)
resourceTypes = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties RecordingGroupProperty where
  toResourceProperties :: RecordingGroupProperty -> ResourceProperties
toResourceProperties RecordingGroupProperty {Maybe (ValueList Text)
Maybe (Value Bool)
Maybe ExclusionByResourceTypesProperty
Maybe RecordingStrategyProperty
()
haddock_workaround_ :: RecordingGroupProperty -> ()
allSupported :: RecordingGroupProperty -> Maybe (Value Bool)
exclusionByResourceTypes :: RecordingGroupProperty -> Maybe ExclusionByResourceTypesProperty
includeGlobalResourceTypes :: RecordingGroupProperty -> Maybe (Value Bool)
recordingStrategy :: RecordingGroupProperty -> Maybe RecordingStrategyProperty
resourceTypes :: RecordingGroupProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
allSupported :: Maybe (Value Bool)
exclusionByResourceTypes :: Maybe ExclusionByResourceTypesProperty
includeGlobalResourceTypes :: Maybe (Value Bool)
recordingStrategy :: Maybe RecordingStrategyProperty
resourceTypes :: Maybe (ValueList Text)
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::Config::ConfigurationRecorder.RecordingGroup",
         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 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
"AllSupported" (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)
allSupported,
                            Key -> ExclusionByResourceTypesProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ExclusionByResourceTypes"
                              (ExclusionByResourceTypesProperty -> (Key, Value))
-> Maybe ExclusionByResourceTypesProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ExclusionByResourceTypesProperty
exclusionByResourceTypes,
                            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
"IncludeGlobalResourceTypes"
                              (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)
includeGlobalResourceTypes,
                            Key -> RecordingStrategyProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RecordingStrategy" (RecordingStrategyProperty -> (Key, Value))
-> Maybe RecordingStrategyProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe RecordingStrategyProperty
recordingStrategy,
                            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..=) Key
"ResourceTypes" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
resourceTypes])}
instance JSON.ToJSON RecordingGroupProperty where
  toJSON :: RecordingGroupProperty -> Value
toJSON RecordingGroupProperty {Maybe (ValueList Text)
Maybe (Value Bool)
Maybe ExclusionByResourceTypesProperty
Maybe RecordingStrategyProperty
()
haddock_workaround_ :: RecordingGroupProperty -> ()
allSupported :: RecordingGroupProperty -> Maybe (Value Bool)
exclusionByResourceTypes :: RecordingGroupProperty -> Maybe ExclusionByResourceTypesProperty
includeGlobalResourceTypes :: RecordingGroupProperty -> Maybe (Value Bool)
recordingStrategy :: RecordingGroupProperty -> Maybe RecordingStrategyProperty
resourceTypes :: RecordingGroupProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
allSupported :: Maybe (Value Bool)
exclusionByResourceTypes :: Maybe ExclusionByResourceTypesProperty
includeGlobalResourceTypes :: Maybe (Value Bool)
recordingStrategy :: Maybe RecordingStrategyProperty
resourceTypes :: Maybe (ValueList Text)
..}
    = [(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 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
"AllSupported" (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)
allSupported,
               Key -> ExclusionByResourceTypesProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ExclusionByResourceTypes"
                 (ExclusionByResourceTypesProperty -> (Key, Value))
-> Maybe ExclusionByResourceTypesProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ExclusionByResourceTypesProperty
exclusionByResourceTypes,
               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
"IncludeGlobalResourceTypes"
                 (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)
includeGlobalResourceTypes,
               Key -> RecordingStrategyProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RecordingStrategy" (RecordingStrategyProperty -> (Key, Value))
-> Maybe RecordingStrategyProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe RecordingStrategyProperty
recordingStrategy,
               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..=) Key
"ResourceTypes" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
resourceTypes]))
instance Property "AllSupported" RecordingGroupProperty where
  type PropertyType "AllSupported" RecordingGroupProperty = Value Prelude.Bool
  set :: PropertyType "AllSupported" RecordingGroupProperty
-> RecordingGroupProperty -> RecordingGroupProperty
set PropertyType "AllSupported" RecordingGroupProperty
newValue RecordingGroupProperty {Maybe (ValueList Text)
Maybe (Value Bool)
Maybe ExclusionByResourceTypesProperty
Maybe RecordingStrategyProperty
()
haddock_workaround_ :: RecordingGroupProperty -> ()
allSupported :: RecordingGroupProperty -> Maybe (Value Bool)
exclusionByResourceTypes :: RecordingGroupProperty -> Maybe ExclusionByResourceTypesProperty
includeGlobalResourceTypes :: RecordingGroupProperty -> Maybe (Value Bool)
recordingStrategy :: RecordingGroupProperty -> Maybe RecordingStrategyProperty
resourceTypes :: RecordingGroupProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
allSupported :: Maybe (Value Bool)
exclusionByResourceTypes :: Maybe ExclusionByResourceTypesProperty
includeGlobalResourceTypes :: Maybe (Value Bool)
recordingStrategy :: Maybe RecordingStrategyProperty
resourceTypes :: Maybe (ValueList Text)
..}
    = RecordingGroupProperty {allSupported :: Maybe (Value Bool)
allSupported = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "AllSupported" RecordingGroupProperty
Value Bool
newValue, Maybe (ValueList Text)
Maybe (Value Bool)
Maybe ExclusionByResourceTypesProperty
Maybe RecordingStrategyProperty
()
haddock_workaround_ :: ()
exclusionByResourceTypes :: Maybe ExclusionByResourceTypesProperty
includeGlobalResourceTypes :: Maybe (Value Bool)
recordingStrategy :: Maybe RecordingStrategyProperty
resourceTypes :: Maybe (ValueList Text)
haddock_workaround_ :: ()
exclusionByResourceTypes :: Maybe ExclusionByResourceTypesProperty
includeGlobalResourceTypes :: Maybe (Value Bool)
recordingStrategy :: Maybe RecordingStrategyProperty
resourceTypes :: Maybe (ValueList Text)
..}
instance Property "ExclusionByResourceTypes" RecordingGroupProperty where
  type PropertyType "ExclusionByResourceTypes" RecordingGroupProperty = ExclusionByResourceTypesProperty
  set :: PropertyType "ExclusionByResourceTypes" RecordingGroupProperty
-> RecordingGroupProperty -> RecordingGroupProperty
set PropertyType "ExclusionByResourceTypes" RecordingGroupProperty
newValue RecordingGroupProperty {Maybe (ValueList Text)
Maybe (Value Bool)
Maybe ExclusionByResourceTypesProperty
Maybe RecordingStrategyProperty
()
haddock_workaround_ :: RecordingGroupProperty -> ()
allSupported :: RecordingGroupProperty -> Maybe (Value Bool)
exclusionByResourceTypes :: RecordingGroupProperty -> Maybe ExclusionByResourceTypesProperty
includeGlobalResourceTypes :: RecordingGroupProperty -> Maybe (Value Bool)
recordingStrategy :: RecordingGroupProperty -> Maybe RecordingStrategyProperty
resourceTypes :: RecordingGroupProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
allSupported :: Maybe (Value Bool)
exclusionByResourceTypes :: Maybe ExclusionByResourceTypesProperty
includeGlobalResourceTypes :: Maybe (Value Bool)
recordingStrategy :: Maybe RecordingStrategyProperty
resourceTypes :: Maybe (ValueList Text)
..}
    = RecordingGroupProperty
        {exclusionByResourceTypes :: Maybe ExclusionByResourceTypesProperty
exclusionByResourceTypes = ExclusionByResourceTypesProperty
-> Maybe ExclusionByResourceTypesProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ExclusionByResourceTypes" RecordingGroupProperty
ExclusionByResourceTypesProperty
newValue, Maybe (ValueList Text)
Maybe (Value Bool)
Maybe RecordingStrategyProperty
()
haddock_workaround_ :: ()
allSupported :: Maybe (Value Bool)
includeGlobalResourceTypes :: Maybe (Value Bool)
recordingStrategy :: Maybe RecordingStrategyProperty
resourceTypes :: Maybe (ValueList Text)
haddock_workaround_ :: ()
allSupported :: Maybe (Value Bool)
includeGlobalResourceTypes :: Maybe (Value Bool)
recordingStrategy :: Maybe RecordingStrategyProperty
resourceTypes :: Maybe (ValueList Text)
..}
instance Property "IncludeGlobalResourceTypes" RecordingGroupProperty where
  type PropertyType "IncludeGlobalResourceTypes" RecordingGroupProperty = Value Prelude.Bool
  set :: PropertyType "IncludeGlobalResourceTypes" RecordingGroupProperty
-> RecordingGroupProperty -> RecordingGroupProperty
set PropertyType "IncludeGlobalResourceTypes" RecordingGroupProperty
newValue RecordingGroupProperty {Maybe (ValueList Text)
Maybe (Value Bool)
Maybe ExclusionByResourceTypesProperty
Maybe RecordingStrategyProperty
()
haddock_workaround_ :: RecordingGroupProperty -> ()
allSupported :: RecordingGroupProperty -> Maybe (Value Bool)
exclusionByResourceTypes :: RecordingGroupProperty -> Maybe ExclusionByResourceTypesProperty
includeGlobalResourceTypes :: RecordingGroupProperty -> Maybe (Value Bool)
recordingStrategy :: RecordingGroupProperty -> Maybe RecordingStrategyProperty
resourceTypes :: RecordingGroupProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
allSupported :: Maybe (Value Bool)
exclusionByResourceTypes :: Maybe ExclusionByResourceTypesProperty
includeGlobalResourceTypes :: Maybe (Value Bool)
recordingStrategy :: Maybe RecordingStrategyProperty
resourceTypes :: Maybe (ValueList Text)
..}
    = RecordingGroupProperty
        {includeGlobalResourceTypes :: Maybe (Value Bool)
includeGlobalResourceTypes = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "IncludeGlobalResourceTypes" RecordingGroupProperty
Value Bool
newValue, Maybe (ValueList Text)
Maybe (Value Bool)
Maybe ExclusionByResourceTypesProperty
Maybe RecordingStrategyProperty
()
haddock_workaround_ :: ()
allSupported :: Maybe (Value Bool)
exclusionByResourceTypes :: Maybe ExclusionByResourceTypesProperty
recordingStrategy :: Maybe RecordingStrategyProperty
resourceTypes :: Maybe (ValueList Text)
haddock_workaround_ :: ()
allSupported :: Maybe (Value Bool)
exclusionByResourceTypes :: Maybe ExclusionByResourceTypesProperty
recordingStrategy :: Maybe RecordingStrategyProperty
resourceTypes :: Maybe (ValueList Text)
..}
instance Property "RecordingStrategy" RecordingGroupProperty where
  type PropertyType "RecordingStrategy" RecordingGroupProperty = RecordingStrategyProperty
  set :: PropertyType "RecordingStrategy" RecordingGroupProperty
-> RecordingGroupProperty -> RecordingGroupProperty
set PropertyType "RecordingStrategy" RecordingGroupProperty
newValue RecordingGroupProperty {Maybe (ValueList Text)
Maybe (Value Bool)
Maybe ExclusionByResourceTypesProperty
Maybe RecordingStrategyProperty
()
haddock_workaround_ :: RecordingGroupProperty -> ()
allSupported :: RecordingGroupProperty -> Maybe (Value Bool)
exclusionByResourceTypes :: RecordingGroupProperty -> Maybe ExclusionByResourceTypesProperty
includeGlobalResourceTypes :: RecordingGroupProperty -> Maybe (Value Bool)
recordingStrategy :: RecordingGroupProperty -> Maybe RecordingStrategyProperty
resourceTypes :: RecordingGroupProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
allSupported :: Maybe (Value Bool)
exclusionByResourceTypes :: Maybe ExclusionByResourceTypesProperty
includeGlobalResourceTypes :: Maybe (Value Bool)
recordingStrategy :: Maybe RecordingStrategyProperty
resourceTypes :: Maybe (ValueList Text)
..}
    = RecordingGroupProperty
        {recordingStrategy :: Maybe RecordingStrategyProperty
recordingStrategy = RecordingStrategyProperty -> Maybe RecordingStrategyProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "RecordingStrategy" RecordingGroupProperty
RecordingStrategyProperty
newValue, Maybe (ValueList Text)
Maybe (Value Bool)
Maybe ExclusionByResourceTypesProperty
()
haddock_workaround_ :: ()
allSupported :: Maybe (Value Bool)
exclusionByResourceTypes :: Maybe ExclusionByResourceTypesProperty
includeGlobalResourceTypes :: Maybe (Value Bool)
resourceTypes :: Maybe (ValueList Text)
haddock_workaround_ :: ()
allSupported :: Maybe (Value Bool)
exclusionByResourceTypes :: Maybe ExclusionByResourceTypesProperty
includeGlobalResourceTypes :: Maybe (Value Bool)
resourceTypes :: Maybe (ValueList Text)
..}
instance Property "ResourceTypes" RecordingGroupProperty where
  type PropertyType "ResourceTypes" RecordingGroupProperty = ValueList Prelude.Text
  set :: PropertyType "ResourceTypes" RecordingGroupProperty
-> RecordingGroupProperty -> RecordingGroupProperty
set PropertyType "ResourceTypes" RecordingGroupProperty
newValue RecordingGroupProperty {Maybe (ValueList Text)
Maybe (Value Bool)
Maybe ExclusionByResourceTypesProperty
Maybe RecordingStrategyProperty
()
haddock_workaround_ :: RecordingGroupProperty -> ()
allSupported :: RecordingGroupProperty -> Maybe (Value Bool)
exclusionByResourceTypes :: RecordingGroupProperty -> Maybe ExclusionByResourceTypesProperty
includeGlobalResourceTypes :: RecordingGroupProperty -> Maybe (Value Bool)
recordingStrategy :: RecordingGroupProperty -> Maybe RecordingStrategyProperty
resourceTypes :: RecordingGroupProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
allSupported :: Maybe (Value Bool)
exclusionByResourceTypes :: Maybe ExclusionByResourceTypesProperty
includeGlobalResourceTypes :: Maybe (Value Bool)
recordingStrategy :: Maybe RecordingStrategyProperty
resourceTypes :: Maybe (ValueList Text)
..}
    = RecordingGroupProperty
        {resourceTypes :: Maybe (ValueList Text)
resourceTypes = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ResourceTypes" RecordingGroupProperty
ValueList Text
newValue, Maybe (Value Bool)
Maybe ExclusionByResourceTypesProperty
Maybe RecordingStrategyProperty
()
haddock_workaround_ :: ()
allSupported :: Maybe (Value Bool)
exclusionByResourceTypes :: Maybe ExclusionByResourceTypesProperty
includeGlobalResourceTypes :: Maybe (Value Bool)
recordingStrategy :: Maybe RecordingStrategyProperty
haddock_workaround_ :: ()
allSupported :: Maybe (Value Bool)
exclusionByResourceTypes :: Maybe ExclusionByResourceTypesProperty
includeGlobalResourceTypes :: Maybe (Value Bool)
recordingStrategy :: Maybe RecordingStrategyProperty
..}