module Stratosphere.QuickSight.DataSet.RefreshConfigurationProperty (
module Exports, RefreshConfigurationProperty(..),
mkRefreshConfigurationProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.QuickSight.DataSet.IncrementalRefreshProperty as Exports
import Stratosphere.ResourceProperties
data RefreshConfigurationProperty
=
RefreshConfigurationProperty {RefreshConfigurationProperty -> ()
haddock_workaround_ :: (),
RefreshConfigurationProperty -> IncrementalRefreshProperty
incrementalRefresh :: IncrementalRefreshProperty}
deriving stock (RefreshConfigurationProperty
-> RefreshConfigurationProperty -> Bool
(RefreshConfigurationProperty
-> RefreshConfigurationProperty -> Bool)
-> (RefreshConfigurationProperty
-> RefreshConfigurationProperty -> Bool)
-> Eq RefreshConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RefreshConfigurationProperty
-> RefreshConfigurationProperty -> Bool
== :: RefreshConfigurationProperty
-> RefreshConfigurationProperty -> Bool
$c/= :: RefreshConfigurationProperty
-> RefreshConfigurationProperty -> Bool
/= :: RefreshConfigurationProperty
-> RefreshConfigurationProperty -> Bool
Prelude.Eq, Int -> RefreshConfigurationProperty -> ShowS
[RefreshConfigurationProperty] -> ShowS
RefreshConfigurationProperty -> String
(Int -> RefreshConfigurationProperty -> ShowS)
-> (RefreshConfigurationProperty -> String)
-> ([RefreshConfigurationProperty] -> ShowS)
-> Show RefreshConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RefreshConfigurationProperty -> ShowS
showsPrec :: Int -> RefreshConfigurationProperty -> ShowS
$cshow :: RefreshConfigurationProperty -> String
show :: RefreshConfigurationProperty -> String
$cshowList :: [RefreshConfigurationProperty] -> ShowS
showList :: [RefreshConfigurationProperty] -> ShowS
Prelude.Show)
mkRefreshConfigurationProperty ::
IncrementalRefreshProperty -> RefreshConfigurationProperty
mkRefreshConfigurationProperty :: IncrementalRefreshProperty -> RefreshConfigurationProperty
mkRefreshConfigurationProperty IncrementalRefreshProperty
incrementalRefresh
= RefreshConfigurationProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), incrementalRefresh :: IncrementalRefreshProperty
incrementalRefresh = IncrementalRefreshProperty
incrementalRefresh}
instance ToResourceProperties RefreshConfigurationProperty where
toResourceProperties :: RefreshConfigurationProperty -> ResourceProperties
toResourceProperties RefreshConfigurationProperty {()
IncrementalRefreshProperty
haddock_workaround_ :: RefreshConfigurationProperty -> ()
incrementalRefresh :: RefreshConfigurationProperty -> IncrementalRefreshProperty
haddock_workaround_ :: ()
incrementalRefresh :: IncrementalRefreshProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::QuickSight::DataSet.RefreshConfiguration",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"IncrementalRefresh" Key -> IncrementalRefreshProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= IncrementalRefreshProperty
incrementalRefresh]}
instance JSON.ToJSON RefreshConfigurationProperty where
toJSON :: RefreshConfigurationProperty -> Value
toJSON RefreshConfigurationProperty {()
IncrementalRefreshProperty
haddock_workaround_ :: RefreshConfigurationProperty -> ()
incrementalRefresh :: RefreshConfigurationProperty -> IncrementalRefreshProperty
haddock_workaround_ :: ()
incrementalRefresh :: IncrementalRefreshProperty
..}
= [(Key, Value)] -> Value
JSON.object [Key
"IncrementalRefresh" Key -> IncrementalRefreshProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= IncrementalRefreshProperty
incrementalRefresh]
instance Property "IncrementalRefresh" RefreshConfigurationProperty where
type PropertyType "IncrementalRefresh" RefreshConfigurationProperty = IncrementalRefreshProperty
set :: PropertyType "IncrementalRefresh" RefreshConfigurationProperty
-> RefreshConfigurationProperty -> RefreshConfigurationProperty
set PropertyType "IncrementalRefresh" RefreshConfigurationProperty
newValue RefreshConfigurationProperty {()
IncrementalRefreshProperty
haddock_workaround_ :: RefreshConfigurationProperty -> ()
incrementalRefresh :: RefreshConfigurationProperty -> IncrementalRefreshProperty
haddock_workaround_ :: ()
incrementalRefresh :: IncrementalRefreshProperty
..}
= RefreshConfigurationProperty {incrementalRefresh :: IncrementalRefreshProperty
incrementalRefresh = PropertyType "IncrementalRefresh" RefreshConfigurationProperty
IncrementalRefreshProperty
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}