module Stratosphere.CUR.ReportDefinition (
ReportDefinition(..), mkReportDefinition
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Tag
import Stratosphere.Value
data ReportDefinition
=
ReportDefinition {ReportDefinition -> ()
haddock_workaround_ :: (),
ReportDefinition -> Maybe (ValueList Text)
additionalArtifacts :: (Prelude.Maybe (ValueList Prelude.Text)),
ReportDefinition -> Maybe (ValueList Text)
additionalSchemaElements :: (Prelude.Maybe (ValueList Prelude.Text)),
ReportDefinition -> Maybe (Value Text)
billingViewArn :: (Prelude.Maybe (Value Prelude.Text)),
ReportDefinition -> Value Text
compression :: (Value Prelude.Text),
ReportDefinition -> Value Text
format :: (Value Prelude.Text),
ReportDefinition -> Value Bool
refreshClosedReports :: (Value Prelude.Bool),
ReportDefinition -> Value Text
reportName :: (Value Prelude.Text),
ReportDefinition -> Value Text
reportVersioning :: (Value Prelude.Text),
ReportDefinition -> Value Text
s3Bucket :: (Value Prelude.Text),
ReportDefinition -> Value Text
s3Prefix :: (Value Prelude.Text),
ReportDefinition -> Value Text
s3Region :: (Value Prelude.Text),
ReportDefinition -> Maybe [Tag]
tags :: (Prelude.Maybe [Tag]),
ReportDefinition -> Value Text
timeUnit :: (Value Prelude.Text)}
deriving stock (ReportDefinition -> ReportDefinition -> Bool
(ReportDefinition -> ReportDefinition -> Bool)
-> (ReportDefinition -> ReportDefinition -> Bool)
-> Eq ReportDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ReportDefinition -> ReportDefinition -> Bool
== :: ReportDefinition -> ReportDefinition -> Bool
$c/= :: ReportDefinition -> ReportDefinition -> Bool
/= :: ReportDefinition -> ReportDefinition -> Bool
Prelude.Eq, Int -> ReportDefinition -> ShowS
[ReportDefinition] -> ShowS
ReportDefinition -> String
(Int -> ReportDefinition -> ShowS)
-> (ReportDefinition -> String)
-> ([ReportDefinition] -> ShowS)
-> Show ReportDefinition
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ReportDefinition -> ShowS
showsPrec :: Int -> ReportDefinition -> ShowS
$cshow :: ReportDefinition -> String
show :: ReportDefinition -> String
$cshowList :: [ReportDefinition] -> ShowS
showList :: [ReportDefinition] -> ShowS
Prelude.Show)
mkReportDefinition ::
Value Prelude.Text
-> Value Prelude.Text
-> Value Prelude.Bool
-> Value Prelude.Text
-> Value Prelude.Text
-> Value Prelude.Text
-> Value Prelude.Text
-> Value Prelude.Text -> Value Prelude.Text -> ReportDefinition
mkReportDefinition :: Value Text
-> Value Text
-> Value Bool
-> Value Text
-> Value Text
-> Value Text
-> Value Text
-> Value Text
-> Value Text
-> ReportDefinition
mkReportDefinition
Value Text
compression
Value Text
format
Value Bool
refreshClosedReports
Value Text
reportName
Value Text
reportVersioning
Value Text
s3Bucket
Value Text
s3Prefix
Value Text
s3Region
Value Text
timeUnit
= ReportDefinition
{haddock_workaround_ :: ()
haddock_workaround_ = (), compression :: Value Text
compression = Value Text
compression,
format :: Value Text
format = Value Text
format, refreshClosedReports :: Value Bool
refreshClosedReports = Value Bool
refreshClosedReports,
reportName :: Value Text
reportName = Value Text
reportName, reportVersioning :: Value Text
reportVersioning = Value Text
reportVersioning,
s3Bucket :: Value Text
s3Bucket = Value Text
s3Bucket, s3Prefix :: Value Text
s3Prefix = Value Text
s3Prefix, s3Region :: Value Text
s3Region = Value Text
s3Region,
timeUnit :: Value Text
timeUnit = Value Text
timeUnit, additionalArtifacts :: Maybe (ValueList Text)
additionalArtifacts = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing,
additionalSchemaElements :: Maybe (ValueList Text)
additionalSchemaElements = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing,
billingViewArn :: Maybe (Value Text)
billingViewArn = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, tags :: Maybe [Tag]
tags = Maybe [Tag]
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties ReportDefinition where
toResourceProperties :: ReportDefinition -> ResourceProperties
toResourceProperties ReportDefinition {Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Text)
()
Value Bool
Value Text
haddock_workaround_ :: ReportDefinition -> ()
additionalArtifacts :: ReportDefinition -> Maybe (ValueList Text)
additionalSchemaElements :: ReportDefinition -> Maybe (ValueList Text)
billingViewArn :: ReportDefinition -> Maybe (Value Text)
compression :: ReportDefinition -> Value Text
format :: ReportDefinition -> Value Text
refreshClosedReports :: ReportDefinition -> Value Bool
reportName :: ReportDefinition -> Value Text
reportVersioning :: ReportDefinition -> Value Text
s3Bucket :: ReportDefinition -> Value Text
s3Prefix :: ReportDefinition -> Value Text
s3Region :: ReportDefinition -> Value Text
tags :: ReportDefinition -> Maybe [Tag]
timeUnit :: ReportDefinition -> Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::CUR::ReportDefinition",
supportsTags :: Bool
supportsTags = Bool
Prelude.True,
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
"Compression" 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
compression, Key
"Format" 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
format,
Key
"RefreshClosedReports" 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..= Value Bool
refreshClosedReports,
Key
"ReportName" 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
reportName,
Key
"ReportVersioning" 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
reportVersioning,
Key
"S3Bucket" 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
s3Bucket, Key
"S3Prefix" 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
s3Prefix,
Key
"S3Region" 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
s3Region, Key
"TimeUnit" 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
timeUnit]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[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
"AdditionalArtifacts" (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)
additionalArtifacts,
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
"AdditionalSchemaElements"
(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)
additionalSchemaElements,
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
"BillingViewArn" (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)
billingViewArn,
Key -> [Tag] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Tags" ([Tag] -> (Key, Value)) -> Maybe [Tag] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags]))}
instance JSON.ToJSON ReportDefinition where
toJSON :: ReportDefinition -> Value
toJSON ReportDefinition {Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Text)
()
Value Bool
Value Text
haddock_workaround_ :: ReportDefinition -> ()
additionalArtifacts :: ReportDefinition -> Maybe (ValueList Text)
additionalSchemaElements :: ReportDefinition -> Maybe (ValueList Text)
billingViewArn :: ReportDefinition -> Maybe (Value Text)
compression :: ReportDefinition -> Value Text
format :: ReportDefinition -> Value Text
refreshClosedReports :: ReportDefinition -> Value Bool
reportName :: ReportDefinition -> Value Text
reportVersioning :: ReportDefinition -> Value Text
s3Bucket :: ReportDefinition -> Value Text
s3Prefix :: ReportDefinition -> Value Text
s3Region :: ReportDefinition -> Value Text
tags :: ReportDefinition -> Maybe [Tag]
timeUnit :: ReportDefinition -> Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
..}
= [(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
"Compression" 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
compression, Key
"Format" 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
format,
Key
"RefreshClosedReports" 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..= Value Bool
refreshClosedReports,
Key
"ReportName" 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
reportName,
Key
"ReportVersioning" 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
reportVersioning,
Key
"S3Bucket" 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
s3Bucket, Key
"S3Prefix" 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
s3Prefix,
Key
"S3Region" 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
s3Region, Key
"TimeUnit" 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
timeUnit]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[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
"AdditionalArtifacts" (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)
additionalArtifacts,
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
"AdditionalSchemaElements"
(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)
additionalSchemaElements,
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
"BillingViewArn" (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)
billingViewArn,
Key -> [Tag] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Tags" ([Tag] -> (Key, Value)) -> Maybe [Tag] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags])))
instance Property "AdditionalArtifacts" ReportDefinition where
type PropertyType "AdditionalArtifacts" ReportDefinition = ValueList Prelude.Text
set :: PropertyType "AdditionalArtifacts" ReportDefinition
-> ReportDefinition -> ReportDefinition
set PropertyType "AdditionalArtifacts" ReportDefinition
newValue ReportDefinition {Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Text)
()
Value Bool
Value Text
haddock_workaround_ :: ReportDefinition -> ()
additionalArtifacts :: ReportDefinition -> Maybe (ValueList Text)
additionalSchemaElements :: ReportDefinition -> Maybe (ValueList Text)
billingViewArn :: ReportDefinition -> Maybe (Value Text)
compression :: ReportDefinition -> Value Text
format :: ReportDefinition -> Value Text
refreshClosedReports :: ReportDefinition -> Value Bool
reportName :: ReportDefinition -> Value Text
reportVersioning :: ReportDefinition -> Value Text
s3Bucket :: ReportDefinition -> Value Text
s3Prefix :: ReportDefinition -> Value Text
s3Region :: ReportDefinition -> Value Text
tags :: ReportDefinition -> Maybe [Tag]
timeUnit :: ReportDefinition -> Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
..}
= ReportDefinition
{additionalArtifacts :: Maybe (ValueList Text)
additionalArtifacts = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "AdditionalArtifacts" ReportDefinition
ValueList Text
newValue, Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Text)
()
Value Bool
Value Text
haddock_workaround_ :: ()
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
haddock_workaround_ :: ()
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
..}
instance Property "AdditionalSchemaElements" ReportDefinition where
type PropertyType "AdditionalSchemaElements" ReportDefinition = ValueList Prelude.Text
set :: PropertyType "AdditionalSchemaElements" ReportDefinition
-> ReportDefinition -> ReportDefinition
set PropertyType "AdditionalSchemaElements" ReportDefinition
newValue ReportDefinition {Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Text)
()
Value Bool
Value Text
haddock_workaround_ :: ReportDefinition -> ()
additionalArtifacts :: ReportDefinition -> Maybe (ValueList Text)
additionalSchemaElements :: ReportDefinition -> Maybe (ValueList Text)
billingViewArn :: ReportDefinition -> Maybe (Value Text)
compression :: ReportDefinition -> Value Text
format :: ReportDefinition -> Value Text
refreshClosedReports :: ReportDefinition -> Value Bool
reportName :: ReportDefinition -> Value Text
reportVersioning :: ReportDefinition -> Value Text
s3Bucket :: ReportDefinition -> Value Text
s3Prefix :: ReportDefinition -> Value Text
s3Region :: ReportDefinition -> Value Text
tags :: ReportDefinition -> Maybe [Tag]
timeUnit :: ReportDefinition -> Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
..}
= ReportDefinition
{additionalSchemaElements :: Maybe (ValueList Text)
additionalSchemaElements = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "AdditionalSchemaElements" ReportDefinition
ValueList Text
newValue, Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Text)
()
Value Bool
Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
..}
instance Property "BillingViewArn" ReportDefinition where
type PropertyType "BillingViewArn" ReportDefinition = Value Prelude.Text
set :: PropertyType "BillingViewArn" ReportDefinition
-> ReportDefinition -> ReportDefinition
set PropertyType "BillingViewArn" ReportDefinition
newValue ReportDefinition {Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Text)
()
Value Bool
Value Text
haddock_workaround_ :: ReportDefinition -> ()
additionalArtifacts :: ReportDefinition -> Maybe (ValueList Text)
additionalSchemaElements :: ReportDefinition -> Maybe (ValueList Text)
billingViewArn :: ReportDefinition -> Maybe (Value Text)
compression :: ReportDefinition -> Value Text
format :: ReportDefinition -> Value Text
refreshClosedReports :: ReportDefinition -> Value Bool
reportName :: ReportDefinition -> Value Text
reportVersioning :: ReportDefinition -> Value Text
s3Bucket :: ReportDefinition -> Value Text
s3Prefix :: ReportDefinition -> Value Text
s3Region :: ReportDefinition -> Value Text
tags :: ReportDefinition -> Maybe [Tag]
timeUnit :: ReportDefinition -> Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
..}
= ReportDefinition {billingViewArn :: Maybe (Value Text)
billingViewArn = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "BillingViewArn" ReportDefinition
Value Text
newValue, Maybe [Tag]
Maybe (ValueList Text)
()
Value Bool
Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
..}
instance Property "Compression" ReportDefinition where
type PropertyType "Compression" ReportDefinition = Value Prelude.Text
set :: PropertyType "Compression" ReportDefinition
-> ReportDefinition -> ReportDefinition
set PropertyType "Compression" ReportDefinition
newValue ReportDefinition {Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Text)
()
Value Bool
Value Text
haddock_workaround_ :: ReportDefinition -> ()
additionalArtifacts :: ReportDefinition -> Maybe (ValueList Text)
additionalSchemaElements :: ReportDefinition -> Maybe (ValueList Text)
billingViewArn :: ReportDefinition -> Maybe (Value Text)
compression :: ReportDefinition -> Value Text
format :: ReportDefinition -> Value Text
refreshClosedReports :: ReportDefinition -> Value Bool
reportName :: ReportDefinition -> Value Text
reportVersioning :: ReportDefinition -> Value Text
s3Bucket :: ReportDefinition -> Value Text
s3Prefix :: ReportDefinition -> Value Text
s3Region :: ReportDefinition -> Value Text
tags :: ReportDefinition -> Maybe [Tag]
timeUnit :: ReportDefinition -> Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
..}
= ReportDefinition {compression :: Value Text
compression = PropertyType "Compression" ReportDefinition
Value Text
newValue, Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Text)
()
Value Bool
Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
..}
instance Property "Format" ReportDefinition where
type PropertyType "Format" ReportDefinition = Value Prelude.Text
set :: PropertyType "Format" ReportDefinition
-> ReportDefinition -> ReportDefinition
set PropertyType "Format" ReportDefinition
newValue ReportDefinition {Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Text)
()
Value Bool
Value Text
haddock_workaround_ :: ReportDefinition -> ()
additionalArtifacts :: ReportDefinition -> Maybe (ValueList Text)
additionalSchemaElements :: ReportDefinition -> Maybe (ValueList Text)
billingViewArn :: ReportDefinition -> Maybe (Value Text)
compression :: ReportDefinition -> Value Text
format :: ReportDefinition -> Value Text
refreshClosedReports :: ReportDefinition -> Value Bool
reportName :: ReportDefinition -> Value Text
reportVersioning :: ReportDefinition -> Value Text
s3Bucket :: ReportDefinition -> Value Text
s3Prefix :: ReportDefinition -> Value Text
s3Region :: ReportDefinition -> Value Text
tags :: ReportDefinition -> Maybe [Tag]
timeUnit :: ReportDefinition -> Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
..}
= ReportDefinition {format :: Value Text
format = PropertyType "Format" ReportDefinition
Value Text
newValue, Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Text)
()
Value Bool
Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
..}
instance Property "RefreshClosedReports" ReportDefinition where
type PropertyType "RefreshClosedReports" ReportDefinition = Value Prelude.Bool
set :: PropertyType "RefreshClosedReports" ReportDefinition
-> ReportDefinition -> ReportDefinition
set PropertyType "RefreshClosedReports" ReportDefinition
newValue ReportDefinition {Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Text)
()
Value Bool
Value Text
haddock_workaround_ :: ReportDefinition -> ()
additionalArtifacts :: ReportDefinition -> Maybe (ValueList Text)
additionalSchemaElements :: ReportDefinition -> Maybe (ValueList Text)
billingViewArn :: ReportDefinition -> Maybe (Value Text)
compression :: ReportDefinition -> Value Text
format :: ReportDefinition -> Value Text
refreshClosedReports :: ReportDefinition -> Value Bool
reportName :: ReportDefinition -> Value Text
reportVersioning :: ReportDefinition -> Value Text
s3Bucket :: ReportDefinition -> Value Text
s3Prefix :: ReportDefinition -> Value Text
s3Region :: ReportDefinition -> Value Text
tags :: ReportDefinition -> Maybe [Tag]
timeUnit :: ReportDefinition -> Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
..}
= ReportDefinition {refreshClosedReports :: Value Bool
refreshClosedReports = PropertyType "RefreshClosedReports" ReportDefinition
Value Bool
newValue, Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
..}
instance Property "ReportName" ReportDefinition where
type PropertyType "ReportName" ReportDefinition = Value Prelude.Text
set :: PropertyType "ReportName" ReportDefinition
-> ReportDefinition -> ReportDefinition
set PropertyType "ReportName" ReportDefinition
newValue ReportDefinition {Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Text)
()
Value Bool
Value Text
haddock_workaround_ :: ReportDefinition -> ()
additionalArtifacts :: ReportDefinition -> Maybe (ValueList Text)
additionalSchemaElements :: ReportDefinition -> Maybe (ValueList Text)
billingViewArn :: ReportDefinition -> Maybe (Value Text)
compression :: ReportDefinition -> Value Text
format :: ReportDefinition -> Value Text
refreshClosedReports :: ReportDefinition -> Value Bool
reportName :: ReportDefinition -> Value Text
reportVersioning :: ReportDefinition -> Value Text
s3Bucket :: ReportDefinition -> Value Text
s3Prefix :: ReportDefinition -> Value Text
s3Region :: ReportDefinition -> Value Text
tags :: ReportDefinition -> Maybe [Tag]
timeUnit :: ReportDefinition -> Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
..}
= ReportDefinition {reportName :: Value Text
reportName = PropertyType "ReportName" ReportDefinition
Value Text
newValue, Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Text)
()
Value Bool
Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
..}
instance Property "ReportVersioning" ReportDefinition where
type PropertyType "ReportVersioning" ReportDefinition = Value Prelude.Text
set :: PropertyType "ReportVersioning" ReportDefinition
-> ReportDefinition -> ReportDefinition
set PropertyType "ReportVersioning" ReportDefinition
newValue ReportDefinition {Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Text)
()
Value Bool
Value Text
haddock_workaround_ :: ReportDefinition -> ()
additionalArtifacts :: ReportDefinition -> Maybe (ValueList Text)
additionalSchemaElements :: ReportDefinition -> Maybe (ValueList Text)
billingViewArn :: ReportDefinition -> Maybe (Value Text)
compression :: ReportDefinition -> Value Text
format :: ReportDefinition -> Value Text
refreshClosedReports :: ReportDefinition -> Value Bool
reportName :: ReportDefinition -> Value Text
reportVersioning :: ReportDefinition -> Value Text
s3Bucket :: ReportDefinition -> Value Text
s3Prefix :: ReportDefinition -> Value Text
s3Region :: ReportDefinition -> Value Text
tags :: ReportDefinition -> Maybe [Tag]
timeUnit :: ReportDefinition -> Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
..}
= ReportDefinition {reportVersioning :: Value Text
reportVersioning = PropertyType "ReportVersioning" ReportDefinition
Value Text
newValue, Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Text)
()
Value Bool
Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
..}
instance Property "S3Bucket" ReportDefinition where
type PropertyType "S3Bucket" ReportDefinition = Value Prelude.Text
set :: PropertyType "S3Bucket" ReportDefinition
-> ReportDefinition -> ReportDefinition
set PropertyType "S3Bucket" ReportDefinition
newValue ReportDefinition {Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Text)
()
Value Bool
Value Text
haddock_workaround_ :: ReportDefinition -> ()
additionalArtifacts :: ReportDefinition -> Maybe (ValueList Text)
additionalSchemaElements :: ReportDefinition -> Maybe (ValueList Text)
billingViewArn :: ReportDefinition -> Maybe (Value Text)
compression :: ReportDefinition -> Value Text
format :: ReportDefinition -> Value Text
refreshClosedReports :: ReportDefinition -> Value Bool
reportName :: ReportDefinition -> Value Text
reportVersioning :: ReportDefinition -> Value Text
s3Bucket :: ReportDefinition -> Value Text
s3Prefix :: ReportDefinition -> Value Text
s3Region :: ReportDefinition -> Value Text
tags :: ReportDefinition -> Maybe [Tag]
timeUnit :: ReportDefinition -> Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
..}
= ReportDefinition {s3Bucket :: Value Text
s3Bucket = PropertyType "S3Bucket" ReportDefinition
Value Text
newValue, Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Text)
()
Value Bool
Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
..}
instance Property "S3Prefix" ReportDefinition where
type PropertyType "S3Prefix" ReportDefinition = Value Prelude.Text
set :: PropertyType "S3Prefix" ReportDefinition
-> ReportDefinition -> ReportDefinition
set PropertyType "S3Prefix" ReportDefinition
newValue ReportDefinition {Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Text)
()
Value Bool
Value Text
haddock_workaround_ :: ReportDefinition -> ()
additionalArtifacts :: ReportDefinition -> Maybe (ValueList Text)
additionalSchemaElements :: ReportDefinition -> Maybe (ValueList Text)
billingViewArn :: ReportDefinition -> Maybe (Value Text)
compression :: ReportDefinition -> Value Text
format :: ReportDefinition -> Value Text
refreshClosedReports :: ReportDefinition -> Value Bool
reportName :: ReportDefinition -> Value Text
reportVersioning :: ReportDefinition -> Value Text
s3Bucket :: ReportDefinition -> Value Text
s3Prefix :: ReportDefinition -> Value Text
s3Region :: ReportDefinition -> Value Text
tags :: ReportDefinition -> Maybe [Tag]
timeUnit :: ReportDefinition -> Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
..}
= ReportDefinition {s3Prefix :: Value Text
s3Prefix = PropertyType "S3Prefix" ReportDefinition
Value Text
newValue, Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Text)
()
Value Bool
Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
..}
instance Property "S3Region" ReportDefinition where
type PropertyType "S3Region" ReportDefinition = Value Prelude.Text
set :: PropertyType "S3Region" ReportDefinition
-> ReportDefinition -> ReportDefinition
set PropertyType "S3Region" ReportDefinition
newValue ReportDefinition {Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Text)
()
Value Bool
Value Text
haddock_workaround_ :: ReportDefinition -> ()
additionalArtifacts :: ReportDefinition -> Maybe (ValueList Text)
additionalSchemaElements :: ReportDefinition -> Maybe (ValueList Text)
billingViewArn :: ReportDefinition -> Maybe (Value Text)
compression :: ReportDefinition -> Value Text
format :: ReportDefinition -> Value Text
refreshClosedReports :: ReportDefinition -> Value Bool
reportName :: ReportDefinition -> Value Text
reportVersioning :: ReportDefinition -> Value Text
s3Bucket :: ReportDefinition -> Value Text
s3Prefix :: ReportDefinition -> Value Text
s3Region :: ReportDefinition -> Value Text
tags :: ReportDefinition -> Maybe [Tag]
timeUnit :: ReportDefinition -> Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
..}
= ReportDefinition {s3Region :: Value Text
s3Region = PropertyType "S3Region" ReportDefinition
Value Text
newValue, Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Text)
()
Value Bool
Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
..}
instance Property "Tags" ReportDefinition where
type PropertyType "Tags" ReportDefinition = [Tag]
set :: PropertyType "Tags" ReportDefinition
-> ReportDefinition -> ReportDefinition
set PropertyType "Tags" ReportDefinition
newValue ReportDefinition {Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Text)
()
Value Bool
Value Text
haddock_workaround_ :: ReportDefinition -> ()
additionalArtifacts :: ReportDefinition -> Maybe (ValueList Text)
additionalSchemaElements :: ReportDefinition -> Maybe (ValueList Text)
billingViewArn :: ReportDefinition -> Maybe (Value Text)
compression :: ReportDefinition -> Value Text
format :: ReportDefinition -> Value Text
refreshClosedReports :: ReportDefinition -> Value Bool
reportName :: ReportDefinition -> Value Text
reportVersioning :: ReportDefinition -> Value Text
s3Bucket :: ReportDefinition -> Value Text
s3Prefix :: ReportDefinition -> Value Text
s3Region :: ReportDefinition -> Value Text
tags :: ReportDefinition -> Maybe [Tag]
timeUnit :: ReportDefinition -> Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
..}
= ReportDefinition {tags :: Maybe [Tag]
tags = [Tag] -> Maybe [Tag]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [Tag]
PropertyType "Tags" ReportDefinition
newValue, Maybe (ValueList Text)
Maybe (Value Text)
()
Value Bool
Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
timeUnit :: Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
timeUnit :: Value Text
..}
instance Property "TimeUnit" ReportDefinition where
type PropertyType "TimeUnit" ReportDefinition = Value Prelude.Text
set :: PropertyType "TimeUnit" ReportDefinition
-> ReportDefinition -> ReportDefinition
set PropertyType "TimeUnit" ReportDefinition
newValue ReportDefinition {Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Text)
()
Value Bool
Value Text
haddock_workaround_ :: ReportDefinition -> ()
additionalArtifacts :: ReportDefinition -> Maybe (ValueList Text)
additionalSchemaElements :: ReportDefinition -> Maybe (ValueList Text)
billingViewArn :: ReportDefinition -> Maybe (Value Text)
compression :: ReportDefinition -> Value Text
format :: ReportDefinition -> Value Text
refreshClosedReports :: ReportDefinition -> Value Bool
reportName :: ReportDefinition -> Value Text
reportVersioning :: ReportDefinition -> Value Text
s3Bucket :: ReportDefinition -> Value Text
s3Prefix :: ReportDefinition -> Value Text
s3Region :: ReportDefinition -> Value Text
tags :: ReportDefinition -> Maybe [Tag]
timeUnit :: ReportDefinition -> Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
timeUnit :: Value Text
..}
= ReportDefinition {timeUnit :: Value Text
timeUnit = PropertyType "TimeUnit" ReportDefinition
Value Text
newValue, Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Text)
()
Value Bool
Value Text
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
haddock_workaround_ :: ()
additionalArtifacts :: Maybe (ValueList Text)
additionalSchemaElements :: Maybe (ValueList Text)
billingViewArn :: Maybe (Value Text)
compression :: Value Text
format :: Value Text
refreshClosedReports :: Value Bool
reportName :: Value Text
reportVersioning :: Value Text
s3Bucket :: Value Text
s3Prefix :: Value Text
s3Region :: Value Text
tags :: Maybe [Tag]
..}