module Stratosphere.DataBrew.Job.StatisticsConfigurationProperty (
module Exports, StatisticsConfigurationProperty(..),
mkStatisticsConfigurationProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.DataBrew.Job.StatisticOverrideProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data StatisticsConfigurationProperty
=
StatisticsConfigurationProperty {StatisticsConfigurationProperty -> ()
haddock_workaround_ :: (),
StatisticsConfigurationProperty -> Maybe (ValueList Text)
includedStatistics :: (Prelude.Maybe (ValueList Prelude.Text)),
StatisticsConfigurationProperty
-> Maybe [StatisticOverrideProperty]
overrides :: (Prelude.Maybe [StatisticOverrideProperty])}
deriving stock (StatisticsConfigurationProperty
-> StatisticsConfigurationProperty -> Bool
(StatisticsConfigurationProperty
-> StatisticsConfigurationProperty -> Bool)
-> (StatisticsConfigurationProperty
-> StatisticsConfigurationProperty -> Bool)
-> Eq StatisticsConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StatisticsConfigurationProperty
-> StatisticsConfigurationProperty -> Bool
== :: StatisticsConfigurationProperty
-> StatisticsConfigurationProperty -> Bool
$c/= :: StatisticsConfigurationProperty
-> StatisticsConfigurationProperty -> Bool
/= :: StatisticsConfigurationProperty
-> StatisticsConfigurationProperty -> Bool
Prelude.Eq, Int -> StatisticsConfigurationProperty -> ShowS
[StatisticsConfigurationProperty] -> ShowS
StatisticsConfigurationProperty -> String
(Int -> StatisticsConfigurationProperty -> ShowS)
-> (StatisticsConfigurationProperty -> String)
-> ([StatisticsConfigurationProperty] -> ShowS)
-> Show StatisticsConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StatisticsConfigurationProperty -> ShowS
showsPrec :: Int -> StatisticsConfigurationProperty -> ShowS
$cshow :: StatisticsConfigurationProperty -> String
show :: StatisticsConfigurationProperty -> String
$cshowList :: [StatisticsConfigurationProperty] -> ShowS
showList :: [StatisticsConfigurationProperty] -> ShowS
Prelude.Show)
mkStatisticsConfigurationProperty ::
StatisticsConfigurationProperty
mkStatisticsConfigurationProperty :: StatisticsConfigurationProperty
mkStatisticsConfigurationProperty
= StatisticsConfigurationProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), includedStatistics :: Maybe (ValueList Text)
includedStatistics = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing,
overrides :: Maybe [StatisticOverrideProperty]
overrides = Maybe [StatisticOverrideProperty]
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties StatisticsConfigurationProperty where
toResourceProperties :: StatisticsConfigurationProperty -> ResourceProperties
toResourceProperties StatisticsConfigurationProperty {Maybe [StatisticOverrideProperty]
Maybe (ValueList Text)
()
haddock_workaround_ :: StatisticsConfigurationProperty -> ()
includedStatistics :: StatisticsConfigurationProperty -> Maybe (ValueList Text)
overrides :: StatisticsConfigurationProperty
-> Maybe [StatisticOverrideProperty]
haddock_workaround_ :: ()
includedStatistics :: Maybe (ValueList Text)
overrides :: Maybe [StatisticOverrideProperty]
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::DataBrew::Job.StatisticsConfiguration",
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 -> 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
"IncludedStatistics" (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)
includedStatistics,
Key -> [StatisticOverrideProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Overrides" ([StatisticOverrideProperty] -> (Key, Value))
-> Maybe [StatisticOverrideProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [StatisticOverrideProperty]
overrides])}
instance JSON.ToJSON StatisticsConfigurationProperty where
toJSON :: StatisticsConfigurationProperty -> Value
toJSON StatisticsConfigurationProperty {Maybe [StatisticOverrideProperty]
Maybe (ValueList Text)
()
haddock_workaround_ :: StatisticsConfigurationProperty -> ()
includedStatistics :: StatisticsConfigurationProperty -> Maybe (ValueList Text)
overrides :: StatisticsConfigurationProperty
-> Maybe [StatisticOverrideProperty]
haddock_workaround_ :: ()
includedStatistics :: Maybe (ValueList Text)
overrides :: Maybe [StatisticOverrideProperty]
..}
= [(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 -> 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
"IncludedStatistics" (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)
includedStatistics,
Key -> [StatisticOverrideProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Overrides" ([StatisticOverrideProperty] -> (Key, Value))
-> Maybe [StatisticOverrideProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [StatisticOverrideProperty]
overrides]))
instance Property "IncludedStatistics" StatisticsConfigurationProperty where
type PropertyType "IncludedStatistics" StatisticsConfigurationProperty = ValueList Prelude.Text
set :: PropertyType "IncludedStatistics" StatisticsConfigurationProperty
-> StatisticsConfigurationProperty
-> StatisticsConfigurationProperty
set PropertyType "IncludedStatistics" StatisticsConfigurationProperty
newValue StatisticsConfigurationProperty {Maybe [StatisticOverrideProperty]
Maybe (ValueList Text)
()
haddock_workaround_ :: StatisticsConfigurationProperty -> ()
includedStatistics :: StatisticsConfigurationProperty -> Maybe (ValueList Text)
overrides :: StatisticsConfigurationProperty
-> Maybe [StatisticOverrideProperty]
haddock_workaround_ :: ()
includedStatistics :: Maybe (ValueList Text)
overrides :: Maybe [StatisticOverrideProperty]
..}
= StatisticsConfigurationProperty
{includedStatistics :: Maybe (ValueList Text)
includedStatistics = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "IncludedStatistics" StatisticsConfigurationProperty
ValueList Text
newValue, Maybe [StatisticOverrideProperty]
()
haddock_workaround_ :: ()
overrides :: Maybe [StatisticOverrideProperty]
haddock_workaround_ :: ()
overrides :: Maybe [StatisticOverrideProperty]
..}
instance Property "Overrides" StatisticsConfigurationProperty where
type PropertyType "Overrides" StatisticsConfigurationProperty = [StatisticOverrideProperty]
set :: PropertyType "Overrides" StatisticsConfigurationProperty
-> StatisticsConfigurationProperty
-> StatisticsConfigurationProperty
set PropertyType "Overrides" StatisticsConfigurationProperty
newValue StatisticsConfigurationProperty {Maybe [StatisticOverrideProperty]
Maybe (ValueList Text)
()
haddock_workaround_ :: StatisticsConfigurationProperty -> ()
includedStatistics :: StatisticsConfigurationProperty -> Maybe (ValueList Text)
overrides :: StatisticsConfigurationProperty
-> Maybe [StatisticOverrideProperty]
haddock_workaround_ :: ()
includedStatistics :: Maybe (ValueList Text)
overrides :: Maybe [StatisticOverrideProperty]
..}
= StatisticsConfigurationProperty
{overrides :: Maybe [StatisticOverrideProperty]
overrides = [StatisticOverrideProperty] -> Maybe [StatisticOverrideProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [StatisticOverrideProperty]
PropertyType "Overrides" StatisticsConfigurationProperty
newValue, Maybe (ValueList Text)
()
haddock_workaround_ :: ()
includedStatistics :: Maybe (ValueList Text)
haddock_workaround_ :: ()
includedStatistics :: Maybe (ValueList Text)
..}