module Stratosphere.Budgets.Budget.NotificationWithSubscribersProperty (
        module Exports, NotificationWithSubscribersProperty(..),
        mkNotificationWithSubscribersProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Budgets.Budget.NotificationProperty as Exports
import {-# SOURCE #-} Stratosphere.Budgets.Budget.SubscriberProperty as Exports
import Stratosphere.ResourceProperties
data NotificationWithSubscribersProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-budgets-budget-notificationwithsubscribers.html>
    NotificationWithSubscribersProperty {NotificationWithSubscribersProperty -> ()
haddock_workaround_ :: (),
                                         -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-budgets-budget-notificationwithsubscribers.html#cfn-budgets-budget-notificationwithsubscribers-notification>
                                         NotificationWithSubscribersProperty -> NotificationProperty
notification :: NotificationProperty,
                                         -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-budgets-budget-notificationwithsubscribers.html#cfn-budgets-budget-notificationwithsubscribers-subscribers>
                                         NotificationWithSubscribersProperty -> [SubscriberProperty]
subscribers :: [SubscriberProperty]}
  deriving stock (NotificationWithSubscribersProperty
-> NotificationWithSubscribersProperty -> Bool
(NotificationWithSubscribersProperty
 -> NotificationWithSubscribersProperty -> Bool)
-> (NotificationWithSubscribersProperty
    -> NotificationWithSubscribersProperty -> Bool)
-> Eq NotificationWithSubscribersProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NotificationWithSubscribersProperty
-> NotificationWithSubscribersProperty -> Bool
== :: NotificationWithSubscribersProperty
-> NotificationWithSubscribersProperty -> Bool
$c/= :: NotificationWithSubscribersProperty
-> NotificationWithSubscribersProperty -> Bool
/= :: NotificationWithSubscribersProperty
-> NotificationWithSubscribersProperty -> Bool
Prelude.Eq, Int -> NotificationWithSubscribersProperty -> ShowS
[NotificationWithSubscribersProperty] -> ShowS
NotificationWithSubscribersProperty -> String
(Int -> NotificationWithSubscribersProperty -> ShowS)
-> (NotificationWithSubscribersProperty -> String)
-> ([NotificationWithSubscribersProperty] -> ShowS)
-> Show NotificationWithSubscribersProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NotificationWithSubscribersProperty -> ShowS
showsPrec :: Int -> NotificationWithSubscribersProperty -> ShowS
$cshow :: NotificationWithSubscribersProperty -> String
show :: NotificationWithSubscribersProperty -> String
$cshowList :: [NotificationWithSubscribersProperty] -> ShowS
showList :: [NotificationWithSubscribersProperty] -> ShowS
Prelude.Show)
mkNotificationWithSubscribersProperty ::
  NotificationProperty
  -> [SubscriberProperty] -> NotificationWithSubscribersProperty
mkNotificationWithSubscribersProperty :: NotificationProperty
-> [SubscriberProperty] -> NotificationWithSubscribersProperty
mkNotificationWithSubscribersProperty NotificationProperty
notification [SubscriberProperty]
subscribers
  = NotificationWithSubscribersProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), notification :: NotificationProperty
notification = NotificationProperty
notification,
       subscribers :: [SubscriberProperty]
subscribers = [SubscriberProperty]
subscribers}
instance ToResourceProperties NotificationWithSubscribersProperty where
  toResourceProperties :: NotificationWithSubscribersProperty -> ResourceProperties
toResourceProperties NotificationWithSubscribersProperty {[SubscriberProperty]
()
NotificationProperty
haddock_workaround_ :: NotificationWithSubscribersProperty -> ()
notification :: NotificationWithSubscribersProperty -> NotificationProperty
subscribers :: NotificationWithSubscribersProperty -> [SubscriberProperty]
haddock_workaround_ :: ()
notification :: NotificationProperty
subscribers :: [SubscriberProperty]
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::Budgets::Budget.NotificationWithSubscribers",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"Notification" Key -> NotificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= NotificationProperty
notification,
                       Key
"Subscribers" Key -> [SubscriberProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [SubscriberProperty]
subscribers]}
instance JSON.ToJSON NotificationWithSubscribersProperty where
  toJSON :: NotificationWithSubscribersProperty -> Value
toJSON NotificationWithSubscribersProperty {[SubscriberProperty]
()
NotificationProperty
haddock_workaround_ :: NotificationWithSubscribersProperty -> ()
notification :: NotificationWithSubscribersProperty -> NotificationProperty
subscribers :: NotificationWithSubscribersProperty -> [SubscriberProperty]
haddock_workaround_ :: ()
notification :: NotificationProperty
subscribers :: [SubscriberProperty]
..}
    = [(Key, Value)] -> Value
JSON.object
        [Key
"Notification" Key -> NotificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= NotificationProperty
notification,
         Key
"Subscribers" Key -> [SubscriberProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [SubscriberProperty]
subscribers]
instance Property "Notification" NotificationWithSubscribersProperty where
  type PropertyType "Notification" NotificationWithSubscribersProperty = NotificationProperty
  set :: PropertyType "Notification" NotificationWithSubscribersProperty
-> NotificationWithSubscribersProperty
-> NotificationWithSubscribersProperty
set PropertyType "Notification" NotificationWithSubscribersProperty
newValue NotificationWithSubscribersProperty {[SubscriberProperty]
()
NotificationProperty
haddock_workaround_ :: NotificationWithSubscribersProperty -> ()
notification :: NotificationWithSubscribersProperty -> NotificationProperty
subscribers :: NotificationWithSubscribersProperty -> [SubscriberProperty]
haddock_workaround_ :: ()
notification :: NotificationProperty
subscribers :: [SubscriberProperty]
..}
    = NotificationWithSubscribersProperty {notification :: NotificationProperty
notification = PropertyType "Notification" NotificationWithSubscribersProperty
NotificationProperty
newValue, [SubscriberProperty]
()
haddock_workaround_ :: ()
subscribers :: [SubscriberProperty]
haddock_workaround_ :: ()
subscribers :: [SubscriberProperty]
..}
instance Property "Subscribers" NotificationWithSubscribersProperty where
  type PropertyType "Subscribers" NotificationWithSubscribersProperty = [SubscriberProperty]
  set :: PropertyType "Subscribers" NotificationWithSubscribersProperty
-> NotificationWithSubscribersProperty
-> NotificationWithSubscribersProperty
set PropertyType "Subscribers" NotificationWithSubscribersProperty
newValue NotificationWithSubscribersProperty {[SubscriberProperty]
()
NotificationProperty
haddock_workaround_ :: NotificationWithSubscribersProperty -> ()
notification :: NotificationWithSubscribersProperty -> NotificationProperty
subscribers :: NotificationWithSubscribersProperty -> [SubscriberProperty]
haddock_workaround_ :: ()
notification :: NotificationProperty
subscribers :: [SubscriberProperty]
..}
    = NotificationWithSubscribersProperty {subscribers :: [SubscriberProperty]
subscribers = [SubscriberProperty]
PropertyType "Subscribers" NotificationWithSubscribersProperty
newValue, ()
NotificationProperty
haddock_workaround_ :: ()
notification :: NotificationProperty
haddock_workaround_ :: ()
notification :: NotificationProperty
..}