module Stratosphere.Pinpoint.ApplicationSettings (
module Exports, ApplicationSettings(..), mkApplicationSettings
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Pinpoint.ApplicationSettings.CampaignHookProperty as Exports
import {-# SOURCE #-} Stratosphere.Pinpoint.ApplicationSettings.LimitsProperty as Exports
import {-# SOURCE #-} Stratosphere.Pinpoint.ApplicationSettings.QuietTimeProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data ApplicationSettings
=
ApplicationSettings {ApplicationSettings -> ()
haddock_workaround_ :: (),
ApplicationSettings -> Value Text
applicationId :: (Value Prelude.Text),
ApplicationSettings -> Maybe CampaignHookProperty
campaignHook :: (Prelude.Maybe CampaignHookProperty),
ApplicationSettings -> Maybe (Value Bool)
cloudWatchMetricsEnabled :: (Prelude.Maybe (Value Prelude.Bool)),
ApplicationSettings -> Maybe LimitsProperty
limits :: (Prelude.Maybe LimitsProperty),
ApplicationSettings -> Maybe QuietTimeProperty
quietTime :: (Prelude.Maybe QuietTimeProperty)}
deriving stock (ApplicationSettings -> ApplicationSettings -> Bool
(ApplicationSettings -> ApplicationSettings -> Bool)
-> (ApplicationSettings -> ApplicationSettings -> Bool)
-> Eq ApplicationSettings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ApplicationSettings -> ApplicationSettings -> Bool
== :: ApplicationSettings -> ApplicationSettings -> Bool
$c/= :: ApplicationSettings -> ApplicationSettings -> Bool
/= :: ApplicationSettings -> ApplicationSettings -> Bool
Prelude.Eq, Int -> ApplicationSettings -> ShowS
[ApplicationSettings] -> ShowS
ApplicationSettings -> String
(Int -> ApplicationSettings -> ShowS)
-> (ApplicationSettings -> String)
-> ([ApplicationSettings] -> ShowS)
-> Show ApplicationSettings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ApplicationSettings -> ShowS
showsPrec :: Int -> ApplicationSettings -> ShowS
$cshow :: ApplicationSettings -> String
show :: ApplicationSettings -> String
$cshowList :: [ApplicationSettings] -> ShowS
showList :: [ApplicationSettings] -> ShowS
Prelude.Show)
mkApplicationSettings :: Value Prelude.Text -> ApplicationSettings
mkApplicationSettings :: Value Text -> ApplicationSettings
mkApplicationSettings Value Text
applicationId
= ApplicationSettings
{haddock_workaround_ :: ()
haddock_workaround_ = (), applicationId :: Value Text
applicationId = Value Text
applicationId,
campaignHook :: Maybe CampaignHookProperty
campaignHook = Maybe CampaignHookProperty
forall a. Maybe a
Prelude.Nothing,
cloudWatchMetricsEnabled :: Maybe (Value Bool)
cloudWatchMetricsEnabled = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
limits :: Maybe LimitsProperty
limits = Maybe LimitsProperty
forall a. Maybe a
Prelude.Nothing, quietTime :: Maybe QuietTimeProperty
quietTime = Maybe QuietTimeProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties ApplicationSettings where
toResourceProperties :: ApplicationSettings -> ResourceProperties
toResourceProperties ApplicationSettings {Maybe (Value Bool)
Maybe CampaignHookProperty
Maybe LimitsProperty
Maybe QuietTimeProperty
()
Value Text
haddock_workaround_ :: ApplicationSettings -> ()
applicationId :: ApplicationSettings -> Value Text
campaignHook :: ApplicationSettings -> Maybe CampaignHookProperty
cloudWatchMetricsEnabled :: ApplicationSettings -> Maybe (Value Bool)
limits :: ApplicationSettings -> Maybe LimitsProperty
quietTime :: ApplicationSettings -> Maybe QuietTimeProperty
haddock_workaround_ :: ()
applicationId :: Value Text
campaignHook :: Maybe CampaignHookProperty
cloudWatchMetricsEnabled :: Maybe (Value Bool)
limits :: Maybe LimitsProperty
quietTime :: Maybe QuietTimeProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::Pinpoint::ApplicationSettings",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
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
"ApplicationId" 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
applicationId]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> CampaignHookProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CampaignHook" (CampaignHookProperty -> (Key, Value))
-> Maybe CampaignHookProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CampaignHookProperty
campaignHook,
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
"CloudWatchMetricsEnabled"
(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)
cloudWatchMetricsEnabled,
Key -> LimitsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Limits" (LimitsProperty -> (Key, Value))
-> Maybe LimitsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe LimitsProperty
limits,
Key -> QuietTimeProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"QuietTime" (QuietTimeProperty -> (Key, Value))
-> Maybe QuietTimeProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe QuietTimeProperty
quietTime]))}
instance JSON.ToJSON ApplicationSettings where
toJSON :: ApplicationSettings -> Value
toJSON ApplicationSettings {Maybe (Value Bool)
Maybe CampaignHookProperty
Maybe LimitsProperty
Maybe QuietTimeProperty
()
Value Text
haddock_workaround_ :: ApplicationSettings -> ()
applicationId :: ApplicationSettings -> Value Text
campaignHook :: ApplicationSettings -> Maybe CampaignHookProperty
cloudWatchMetricsEnabled :: ApplicationSettings -> Maybe (Value Bool)
limits :: ApplicationSettings -> Maybe LimitsProperty
quietTime :: ApplicationSettings -> Maybe QuietTimeProperty
haddock_workaround_ :: ()
applicationId :: Value Text
campaignHook :: Maybe CampaignHookProperty
cloudWatchMetricsEnabled :: Maybe (Value Bool)
limits :: Maybe LimitsProperty
quietTime :: Maybe QuietTimeProperty
..}
= [(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
"ApplicationId" 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
applicationId]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> CampaignHookProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CampaignHook" (CampaignHookProperty -> (Key, Value))
-> Maybe CampaignHookProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CampaignHookProperty
campaignHook,
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
"CloudWatchMetricsEnabled"
(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)
cloudWatchMetricsEnabled,
Key -> LimitsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Limits" (LimitsProperty -> (Key, Value))
-> Maybe LimitsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe LimitsProperty
limits,
Key -> QuietTimeProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"QuietTime" (QuietTimeProperty -> (Key, Value))
-> Maybe QuietTimeProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe QuietTimeProperty
quietTime])))
instance Property "ApplicationId" ApplicationSettings where
type PropertyType "ApplicationId" ApplicationSettings = Value Prelude.Text
set :: PropertyType "ApplicationId" ApplicationSettings
-> ApplicationSettings -> ApplicationSettings
set PropertyType "ApplicationId" ApplicationSettings
newValue ApplicationSettings {Maybe (Value Bool)
Maybe CampaignHookProperty
Maybe LimitsProperty
Maybe QuietTimeProperty
()
Value Text
haddock_workaround_ :: ApplicationSettings -> ()
applicationId :: ApplicationSettings -> Value Text
campaignHook :: ApplicationSettings -> Maybe CampaignHookProperty
cloudWatchMetricsEnabled :: ApplicationSettings -> Maybe (Value Bool)
limits :: ApplicationSettings -> Maybe LimitsProperty
quietTime :: ApplicationSettings -> Maybe QuietTimeProperty
haddock_workaround_ :: ()
applicationId :: Value Text
campaignHook :: Maybe CampaignHookProperty
cloudWatchMetricsEnabled :: Maybe (Value Bool)
limits :: Maybe LimitsProperty
quietTime :: Maybe QuietTimeProperty
..}
= ApplicationSettings {applicationId :: Value Text
applicationId = PropertyType "ApplicationId" ApplicationSettings
Value Text
newValue, Maybe (Value Bool)
Maybe CampaignHookProperty
Maybe LimitsProperty
Maybe QuietTimeProperty
()
haddock_workaround_ :: ()
campaignHook :: Maybe CampaignHookProperty
cloudWatchMetricsEnabled :: Maybe (Value Bool)
limits :: Maybe LimitsProperty
quietTime :: Maybe QuietTimeProperty
haddock_workaround_ :: ()
campaignHook :: Maybe CampaignHookProperty
cloudWatchMetricsEnabled :: Maybe (Value Bool)
limits :: Maybe LimitsProperty
quietTime :: Maybe QuietTimeProperty
..}
instance Property "CampaignHook" ApplicationSettings where
type PropertyType "CampaignHook" ApplicationSettings = CampaignHookProperty
set :: PropertyType "CampaignHook" ApplicationSettings
-> ApplicationSettings -> ApplicationSettings
set PropertyType "CampaignHook" ApplicationSettings
newValue ApplicationSettings {Maybe (Value Bool)
Maybe CampaignHookProperty
Maybe LimitsProperty
Maybe QuietTimeProperty
()
Value Text
haddock_workaround_ :: ApplicationSettings -> ()
applicationId :: ApplicationSettings -> Value Text
campaignHook :: ApplicationSettings -> Maybe CampaignHookProperty
cloudWatchMetricsEnabled :: ApplicationSettings -> Maybe (Value Bool)
limits :: ApplicationSettings -> Maybe LimitsProperty
quietTime :: ApplicationSettings -> Maybe QuietTimeProperty
haddock_workaround_ :: ()
applicationId :: Value Text
campaignHook :: Maybe CampaignHookProperty
cloudWatchMetricsEnabled :: Maybe (Value Bool)
limits :: Maybe LimitsProperty
quietTime :: Maybe QuietTimeProperty
..}
= ApplicationSettings {campaignHook :: Maybe CampaignHookProperty
campaignHook = CampaignHookProperty -> Maybe CampaignHookProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "CampaignHook" ApplicationSettings
CampaignHookProperty
newValue, Maybe (Value Bool)
Maybe LimitsProperty
Maybe QuietTimeProperty
()
Value Text
haddock_workaround_ :: ()
applicationId :: Value Text
cloudWatchMetricsEnabled :: Maybe (Value Bool)
limits :: Maybe LimitsProperty
quietTime :: Maybe QuietTimeProperty
haddock_workaround_ :: ()
applicationId :: Value Text
cloudWatchMetricsEnabled :: Maybe (Value Bool)
limits :: Maybe LimitsProperty
quietTime :: Maybe QuietTimeProperty
..}
instance Property "CloudWatchMetricsEnabled" ApplicationSettings where
type PropertyType "CloudWatchMetricsEnabled" ApplicationSettings = Value Prelude.Bool
set :: PropertyType "CloudWatchMetricsEnabled" ApplicationSettings
-> ApplicationSettings -> ApplicationSettings
set PropertyType "CloudWatchMetricsEnabled" ApplicationSettings
newValue ApplicationSettings {Maybe (Value Bool)
Maybe CampaignHookProperty
Maybe LimitsProperty
Maybe QuietTimeProperty
()
Value Text
haddock_workaround_ :: ApplicationSettings -> ()
applicationId :: ApplicationSettings -> Value Text
campaignHook :: ApplicationSettings -> Maybe CampaignHookProperty
cloudWatchMetricsEnabled :: ApplicationSettings -> Maybe (Value Bool)
limits :: ApplicationSettings -> Maybe LimitsProperty
quietTime :: ApplicationSettings -> Maybe QuietTimeProperty
haddock_workaround_ :: ()
applicationId :: Value Text
campaignHook :: Maybe CampaignHookProperty
cloudWatchMetricsEnabled :: Maybe (Value Bool)
limits :: Maybe LimitsProperty
quietTime :: Maybe QuietTimeProperty
..}
= ApplicationSettings
{cloudWatchMetricsEnabled :: Maybe (Value Bool)
cloudWatchMetricsEnabled = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "CloudWatchMetricsEnabled" ApplicationSettings
Value Bool
newValue, Maybe CampaignHookProperty
Maybe LimitsProperty
Maybe QuietTimeProperty
()
Value Text
haddock_workaround_ :: ()
applicationId :: Value Text
campaignHook :: Maybe CampaignHookProperty
limits :: Maybe LimitsProperty
quietTime :: Maybe QuietTimeProperty
haddock_workaround_ :: ()
applicationId :: Value Text
campaignHook :: Maybe CampaignHookProperty
limits :: Maybe LimitsProperty
quietTime :: Maybe QuietTimeProperty
..}
instance Property "Limits" ApplicationSettings where
type PropertyType "Limits" ApplicationSettings = LimitsProperty
set :: PropertyType "Limits" ApplicationSettings
-> ApplicationSettings -> ApplicationSettings
set PropertyType "Limits" ApplicationSettings
newValue ApplicationSettings {Maybe (Value Bool)
Maybe CampaignHookProperty
Maybe LimitsProperty
Maybe QuietTimeProperty
()
Value Text
haddock_workaround_ :: ApplicationSettings -> ()
applicationId :: ApplicationSettings -> Value Text
campaignHook :: ApplicationSettings -> Maybe CampaignHookProperty
cloudWatchMetricsEnabled :: ApplicationSettings -> Maybe (Value Bool)
limits :: ApplicationSettings -> Maybe LimitsProperty
quietTime :: ApplicationSettings -> Maybe QuietTimeProperty
haddock_workaround_ :: ()
applicationId :: Value Text
campaignHook :: Maybe CampaignHookProperty
cloudWatchMetricsEnabled :: Maybe (Value Bool)
limits :: Maybe LimitsProperty
quietTime :: Maybe QuietTimeProperty
..}
= ApplicationSettings {limits :: Maybe LimitsProperty
limits = LimitsProperty -> Maybe LimitsProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Limits" ApplicationSettings
LimitsProperty
newValue, Maybe (Value Bool)
Maybe CampaignHookProperty
Maybe QuietTimeProperty
()
Value Text
haddock_workaround_ :: ()
applicationId :: Value Text
campaignHook :: Maybe CampaignHookProperty
cloudWatchMetricsEnabled :: Maybe (Value Bool)
quietTime :: Maybe QuietTimeProperty
haddock_workaround_ :: ()
applicationId :: Value Text
campaignHook :: Maybe CampaignHookProperty
cloudWatchMetricsEnabled :: Maybe (Value Bool)
quietTime :: Maybe QuietTimeProperty
..}
instance Property "QuietTime" ApplicationSettings where
type PropertyType "QuietTime" ApplicationSettings = QuietTimeProperty
set :: PropertyType "QuietTime" ApplicationSettings
-> ApplicationSettings -> ApplicationSettings
set PropertyType "QuietTime" ApplicationSettings
newValue ApplicationSettings {Maybe (Value Bool)
Maybe CampaignHookProperty
Maybe LimitsProperty
Maybe QuietTimeProperty
()
Value Text
haddock_workaround_ :: ApplicationSettings -> ()
applicationId :: ApplicationSettings -> Value Text
campaignHook :: ApplicationSettings -> Maybe CampaignHookProperty
cloudWatchMetricsEnabled :: ApplicationSettings -> Maybe (Value Bool)
limits :: ApplicationSettings -> Maybe LimitsProperty
quietTime :: ApplicationSettings -> Maybe QuietTimeProperty
haddock_workaround_ :: ()
applicationId :: Value Text
campaignHook :: Maybe CampaignHookProperty
cloudWatchMetricsEnabled :: Maybe (Value Bool)
limits :: Maybe LimitsProperty
quietTime :: Maybe QuietTimeProperty
..}
= ApplicationSettings {quietTime :: Maybe QuietTimeProperty
quietTime = QuietTimeProperty -> Maybe QuietTimeProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "QuietTime" ApplicationSettings
QuietTimeProperty
newValue, Maybe (Value Bool)
Maybe CampaignHookProperty
Maybe LimitsProperty
()
Value Text
haddock_workaround_ :: ()
applicationId :: Value Text
campaignHook :: Maybe CampaignHookProperty
cloudWatchMetricsEnabled :: Maybe (Value Bool)
limits :: Maybe LimitsProperty
haddock_workaround_ :: ()
applicationId :: Value Text
campaignHook :: Maybe CampaignHookProperty
cloudWatchMetricsEnabled :: Maybe (Value Bool)
limits :: Maybe LimitsProperty
..}