module Stratosphere.Budgets.Budget.SpendProperty (
SpendProperty(..), mkSpendProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data SpendProperty
=
SpendProperty {SpendProperty -> ()
haddock_workaround_ :: (),
SpendProperty -> Value Double
amount :: (Value Prelude.Double),
SpendProperty -> Value Text
unit :: (Value Prelude.Text)}
deriving stock (SpendProperty -> SpendProperty -> Bool
(SpendProperty -> SpendProperty -> Bool)
-> (SpendProperty -> SpendProperty -> Bool) -> Eq SpendProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SpendProperty -> SpendProperty -> Bool
== :: SpendProperty -> SpendProperty -> Bool
$c/= :: SpendProperty -> SpendProperty -> Bool
/= :: SpendProperty -> SpendProperty -> Bool
Prelude.Eq, Int -> SpendProperty -> ShowS
[SpendProperty] -> ShowS
SpendProperty -> String
(Int -> SpendProperty -> ShowS)
-> (SpendProperty -> String)
-> ([SpendProperty] -> ShowS)
-> Show SpendProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SpendProperty -> ShowS
showsPrec :: Int -> SpendProperty -> ShowS
$cshow :: SpendProperty -> String
show :: SpendProperty -> String
$cshowList :: [SpendProperty] -> ShowS
showList :: [SpendProperty] -> ShowS
Prelude.Show)
mkSpendProperty ::
Value Prelude.Double -> Value Prelude.Text -> SpendProperty
mkSpendProperty :: Value Double -> Value Text -> SpendProperty
mkSpendProperty Value Double
amount Value Text
unit
= SpendProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), amount :: Value Double
amount = Value Double
amount, unit :: Value Text
unit = Value Text
unit}
instance ToResourceProperties SpendProperty where
toResourceProperties :: SpendProperty -> ResourceProperties
toResourceProperties SpendProperty {()
Value Double
Value Text
haddock_workaround_ :: SpendProperty -> ()
amount :: SpendProperty -> Value Double
unit :: SpendProperty -> Value Text
haddock_workaround_ :: ()
amount :: Value Double
unit :: Value Text
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::Budgets::Budget.Spend",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"Amount" Key -> Value Double -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Double
amount, Key
"Unit" 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
unit]}
instance JSON.ToJSON SpendProperty where
toJSON :: SpendProperty -> Value
toJSON SpendProperty {()
Value Double
Value Text
haddock_workaround_ :: SpendProperty -> ()
amount :: SpendProperty -> Value Double
unit :: SpendProperty -> Value Text
haddock_workaround_ :: ()
amount :: Value Double
unit :: Value Text
..}
= [(Key, Value)] -> Value
JSON.object [Key
"Amount" Key -> Value Double -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Double
amount, Key
"Unit" 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
unit]
instance Property "Amount" SpendProperty where
type PropertyType "Amount" SpendProperty = Value Prelude.Double
set :: PropertyType "Amount" SpendProperty
-> SpendProperty -> SpendProperty
set PropertyType "Amount" SpendProperty
newValue SpendProperty {()
Value Double
Value Text
haddock_workaround_ :: SpendProperty -> ()
amount :: SpendProperty -> Value Double
unit :: SpendProperty -> Value Text
haddock_workaround_ :: ()
amount :: Value Double
unit :: Value Text
..}
= SpendProperty {amount :: Value Double
amount = PropertyType "Amount" SpendProperty
Value Double
newValue, ()
Value Text
haddock_workaround_ :: ()
unit :: Value Text
haddock_workaround_ :: ()
unit :: Value Text
..}
instance Property "Unit" SpendProperty where
type PropertyType "Unit" SpendProperty = Value Prelude.Text
set :: PropertyType "Unit" SpendProperty -> SpendProperty -> SpendProperty
set PropertyType "Unit" SpendProperty
newValue SpendProperty {()
Value Double
Value Text
haddock_workaround_ :: SpendProperty -> ()
amount :: SpendProperty -> Value Double
unit :: SpendProperty -> Value Text
haddock_workaround_ :: ()
amount :: Value Double
unit :: Value Text
..}
= SpendProperty {unit :: Value Text
unit = PropertyType "Unit" SpendProperty
Value Text
newValue, ()
Value Double
haddock_workaround_ :: ()
amount :: Value Double
haddock_workaround_ :: ()
amount :: Value Double
..}