module Stratosphere.Budgets.Budget.BudgetDataProperty (
        module Exports, BudgetDataProperty(..), mkBudgetDataProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Budgets.Budget.AutoAdjustDataProperty as Exports
import {-# SOURCE #-} Stratosphere.Budgets.Budget.CostTypesProperty as Exports
import {-# SOURCE #-} Stratosphere.Budgets.Budget.ExpressionProperty as Exports
import {-# SOURCE #-} Stratosphere.Budgets.Budget.SpendProperty as Exports
import {-# SOURCE #-} Stratosphere.Budgets.Budget.TimePeriodProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data BudgetDataProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-budgets-budget-budgetdata.html>
    BudgetDataProperty {BudgetDataProperty -> ()
haddock_workaround_ :: (),
                        -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-budgets-budget-budgetdata.html#cfn-budgets-budget-budgetdata-autoadjustdata>
                        BudgetDataProperty -> Maybe AutoAdjustDataProperty
autoAdjustData :: (Prelude.Maybe AutoAdjustDataProperty),
                        -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-budgets-budget-budgetdata.html#cfn-budgets-budget-budgetdata-billingviewarn>
                        BudgetDataProperty -> Maybe (Value Text)
billingViewArn :: (Prelude.Maybe (Value Prelude.Text)),
                        -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-budgets-budget-budgetdata.html#cfn-budgets-budget-budgetdata-budgetlimit>
                        BudgetDataProperty -> Maybe SpendProperty
budgetLimit :: (Prelude.Maybe SpendProperty),
                        -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-budgets-budget-budgetdata.html#cfn-budgets-budget-budgetdata-budgetname>
                        BudgetDataProperty -> Maybe (Value Text)
budgetName :: (Prelude.Maybe (Value Prelude.Text)),
                        -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-budgets-budget-budgetdata.html#cfn-budgets-budget-budgetdata-budgettype>
                        BudgetDataProperty -> Value Text
budgetType :: (Value Prelude.Text),
                        -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-budgets-budget-budgetdata.html#cfn-budgets-budget-budgetdata-costfilters>
                        BudgetDataProperty -> Maybe Object
costFilters :: (Prelude.Maybe JSON.Object),
                        -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-budgets-budget-budgetdata.html#cfn-budgets-budget-budgetdata-costtypes>
                        BudgetDataProperty -> Maybe CostTypesProperty
costTypes :: (Prelude.Maybe CostTypesProperty),
                        -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-budgets-budget-budgetdata.html#cfn-budgets-budget-budgetdata-filterexpression>
                        BudgetDataProperty -> Maybe ExpressionProperty
filterExpression :: (Prelude.Maybe ExpressionProperty),
                        -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-budgets-budget-budgetdata.html#cfn-budgets-budget-budgetdata-metrics>
                        BudgetDataProperty -> Maybe (ValueList Text)
metrics :: (Prelude.Maybe (ValueList Prelude.Text)),
                        -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-budgets-budget-budgetdata.html#cfn-budgets-budget-budgetdata-plannedbudgetlimits>
                        BudgetDataProperty -> Maybe Object
plannedBudgetLimits :: (Prelude.Maybe JSON.Object),
                        -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-budgets-budget-budgetdata.html#cfn-budgets-budget-budgetdata-timeperiod>
                        BudgetDataProperty -> Maybe TimePeriodProperty
timePeriod :: (Prelude.Maybe TimePeriodProperty),
                        -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-budgets-budget-budgetdata.html#cfn-budgets-budget-budgetdata-timeunit>
                        BudgetDataProperty -> Value Text
timeUnit :: (Value Prelude.Text)}
  deriving stock (BudgetDataProperty -> BudgetDataProperty -> Bool
(BudgetDataProperty -> BudgetDataProperty -> Bool)
-> (BudgetDataProperty -> BudgetDataProperty -> Bool)
-> Eq BudgetDataProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BudgetDataProperty -> BudgetDataProperty -> Bool
== :: BudgetDataProperty -> BudgetDataProperty -> Bool
$c/= :: BudgetDataProperty -> BudgetDataProperty -> Bool
/= :: BudgetDataProperty -> BudgetDataProperty -> Bool
Prelude.Eq, Int -> BudgetDataProperty -> ShowS
[BudgetDataProperty] -> ShowS
BudgetDataProperty -> String
(Int -> BudgetDataProperty -> ShowS)
-> (BudgetDataProperty -> String)
-> ([BudgetDataProperty] -> ShowS)
-> Show BudgetDataProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BudgetDataProperty -> ShowS
showsPrec :: Int -> BudgetDataProperty -> ShowS
$cshow :: BudgetDataProperty -> String
show :: BudgetDataProperty -> String
$cshowList :: [BudgetDataProperty] -> ShowS
showList :: [BudgetDataProperty] -> ShowS
Prelude.Show)
mkBudgetDataProperty ::
  Value Prelude.Text -> Value Prelude.Text -> BudgetDataProperty
mkBudgetDataProperty :: Value Text -> Value Text -> BudgetDataProperty
mkBudgetDataProperty Value Text
budgetType Value Text
timeUnit
  = BudgetDataProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), budgetType :: Value Text
budgetType = Value Text
budgetType,
       timeUnit :: Value Text
timeUnit = Value Text
timeUnit, autoAdjustData :: Maybe AutoAdjustDataProperty
autoAdjustData = Maybe AutoAdjustDataProperty
forall a. Maybe a
Prelude.Nothing,
       billingViewArn :: Maybe (Value Text)
billingViewArn = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, budgetLimit :: Maybe SpendProperty
budgetLimit = Maybe SpendProperty
forall a. Maybe a
Prelude.Nothing,
       budgetName :: Maybe (Value Text)
budgetName = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, costFilters :: Maybe Object
costFilters = Maybe Object
forall a. Maybe a
Prelude.Nothing,
       costTypes :: Maybe CostTypesProperty
costTypes = Maybe CostTypesProperty
forall a. Maybe a
Prelude.Nothing, filterExpression :: Maybe ExpressionProperty
filterExpression = Maybe ExpressionProperty
forall a. Maybe a
Prelude.Nothing,
       metrics :: Maybe (ValueList Text)
metrics = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing, plannedBudgetLimits :: Maybe Object
plannedBudgetLimits = Maybe Object
forall a. Maybe a
Prelude.Nothing,
       timePeriod :: Maybe TimePeriodProperty
timePeriod = Maybe TimePeriodProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties BudgetDataProperty where
  toResourceProperties :: BudgetDataProperty -> ResourceProperties
toResourceProperties BudgetDataProperty {Maybe Object
Maybe (ValueList Text)
Maybe (Value Text)
Maybe CostTypesProperty
Maybe AutoAdjustDataProperty
Maybe SpendProperty
Maybe ExpressionProperty
Maybe TimePeriodProperty
()
Value Text
haddock_workaround_ :: BudgetDataProperty -> ()
autoAdjustData :: BudgetDataProperty -> Maybe AutoAdjustDataProperty
billingViewArn :: BudgetDataProperty -> Maybe (Value Text)
budgetLimit :: BudgetDataProperty -> Maybe SpendProperty
budgetName :: BudgetDataProperty -> Maybe (Value Text)
budgetType :: BudgetDataProperty -> Value Text
costFilters :: BudgetDataProperty -> Maybe Object
costTypes :: BudgetDataProperty -> Maybe CostTypesProperty
filterExpression :: BudgetDataProperty -> Maybe ExpressionProperty
metrics :: BudgetDataProperty -> Maybe (ValueList Text)
plannedBudgetLimits :: BudgetDataProperty -> Maybe Object
timePeriod :: BudgetDataProperty -> Maybe TimePeriodProperty
timeUnit :: BudgetDataProperty -> Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::Budgets::Budget.BudgetData",
         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
"BudgetType" 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
budgetType, Key
"TimeUnit" 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
timeUnit]
                           ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                              [Key -> AutoAdjustDataProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AutoAdjustData" (AutoAdjustDataProperty -> (Key, Value))
-> Maybe AutoAdjustDataProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AutoAdjustDataProperty
autoAdjustData,
                               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..=) Key
"BillingViewArn" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
billingViewArn,
                               Key -> SpendProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"BudgetLimit" (SpendProperty -> (Key, Value))
-> Maybe SpendProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SpendProperty
budgetLimit,
                               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..=) Key
"BudgetName" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
budgetName,
                               Key -> Object -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CostFilters" (Object -> (Key, Value)) -> Maybe Object -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Object
costFilters,
                               Key -> CostTypesProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CostTypes" (CostTypesProperty -> (Key, Value))
-> Maybe CostTypesProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CostTypesProperty
costTypes,
                               Key -> ExpressionProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"FilterExpression" (ExpressionProperty -> (Key, Value))
-> Maybe ExpressionProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ExpressionProperty
filterExpression,
                               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
"Metrics" (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)
metrics,
                               Key -> Object -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PlannedBudgetLimits" (Object -> (Key, Value)) -> Maybe Object -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Object
plannedBudgetLimits,
                               Key -> TimePeriodProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"TimePeriod" (TimePeriodProperty -> (Key, Value))
-> Maybe TimePeriodProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe TimePeriodProperty
timePeriod]))}
instance JSON.ToJSON BudgetDataProperty where
  toJSON :: BudgetDataProperty -> Value
toJSON BudgetDataProperty {Maybe Object
Maybe (ValueList Text)
Maybe (Value Text)
Maybe CostTypesProperty
Maybe AutoAdjustDataProperty
Maybe SpendProperty
Maybe ExpressionProperty
Maybe TimePeriodProperty
()
Value Text
haddock_workaround_ :: BudgetDataProperty -> ()
autoAdjustData :: BudgetDataProperty -> Maybe AutoAdjustDataProperty
billingViewArn :: BudgetDataProperty -> Maybe (Value Text)
budgetLimit :: BudgetDataProperty -> Maybe SpendProperty
budgetName :: BudgetDataProperty -> Maybe (Value Text)
budgetType :: BudgetDataProperty -> Value Text
costFilters :: BudgetDataProperty -> Maybe Object
costTypes :: BudgetDataProperty -> Maybe CostTypesProperty
filterExpression :: BudgetDataProperty -> Maybe ExpressionProperty
metrics :: BudgetDataProperty -> Maybe (ValueList Text)
plannedBudgetLimits :: BudgetDataProperty -> Maybe Object
timePeriod :: BudgetDataProperty -> Maybe TimePeriodProperty
timeUnit :: BudgetDataProperty -> Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
..}
    = [(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
"BudgetType" 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
budgetType, Key
"TimeUnit" 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
timeUnit]
              ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                 [Key -> AutoAdjustDataProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AutoAdjustData" (AutoAdjustDataProperty -> (Key, Value))
-> Maybe AutoAdjustDataProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AutoAdjustDataProperty
autoAdjustData,
                  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..=) Key
"BillingViewArn" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
billingViewArn,
                  Key -> SpendProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"BudgetLimit" (SpendProperty -> (Key, Value))
-> Maybe SpendProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SpendProperty
budgetLimit,
                  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..=) Key
"BudgetName" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
budgetName,
                  Key -> Object -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CostFilters" (Object -> (Key, Value)) -> Maybe Object -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Object
costFilters,
                  Key -> CostTypesProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CostTypes" (CostTypesProperty -> (Key, Value))
-> Maybe CostTypesProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CostTypesProperty
costTypes,
                  Key -> ExpressionProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"FilterExpression" (ExpressionProperty -> (Key, Value))
-> Maybe ExpressionProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ExpressionProperty
filterExpression,
                  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
"Metrics" (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)
metrics,
                  Key -> Object -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PlannedBudgetLimits" (Object -> (Key, Value)) -> Maybe Object -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Object
plannedBudgetLimits,
                  Key -> TimePeriodProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"TimePeriod" (TimePeriodProperty -> (Key, Value))
-> Maybe TimePeriodProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe TimePeriodProperty
timePeriod])))
instance Property "AutoAdjustData" BudgetDataProperty where
  type PropertyType "AutoAdjustData" BudgetDataProperty = AutoAdjustDataProperty
  set :: PropertyType "AutoAdjustData" BudgetDataProperty
-> BudgetDataProperty -> BudgetDataProperty
set PropertyType "AutoAdjustData" BudgetDataProperty
newValue BudgetDataProperty {Maybe Object
Maybe (ValueList Text)
Maybe (Value Text)
Maybe CostTypesProperty
Maybe AutoAdjustDataProperty
Maybe SpendProperty
Maybe ExpressionProperty
Maybe TimePeriodProperty
()
Value Text
haddock_workaround_ :: BudgetDataProperty -> ()
autoAdjustData :: BudgetDataProperty -> Maybe AutoAdjustDataProperty
billingViewArn :: BudgetDataProperty -> Maybe (Value Text)
budgetLimit :: BudgetDataProperty -> Maybe SpendProperty
budgetName :: BudgetDataProperty -> Maybe (Value Text)
budgetType :: BudgetDataProperty -> Value Text
costFilters :: BudgetDataProperty -> Maybe Object
costTypes :: BudgetDataProperty -> Maybe CostTypesProperty
filterExpression :: BudgetDataProperty -> Maybe ExpressionProperty
metrics :: BudgetDataProperty -> Maybe (ValueList Text)
plannedBudgetLimits :: BudgetDataProperty -> Maybe Object
timePeriod :: BudgetDataProperty -> Maybe TimePeriodProperty
timeUnit :: BudgetDataProperty -> Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
..}
    = BudgetDataProperty {autoAdjustData :: Maybe AutoAdjustDataProperty
autoAdjustData = AutoAdjustDataProperty -> Maybe AutoAdjustDataProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "AutoAdjustData" BudgetDataProperty
AutoAdjustDataProperty
newValue, Maybe Object
Maybe (ValueList Text)
Maybe (Value Text)
Maybe CostTypesProperty
Maybe SpendProperty
Maybe ExpressionProperty
Maybe TimePeriodProperty
()
Value Text
haddock_workaround_ :: ()
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
haddock_workaround_ :: ()
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
..}
instance Property "BillingViewArn" BudgetDataProperty where
  type PropertyType "BillingViewArn" BudgetDataProperty = Value Prelude.Text
  set :: PropertyType "BillingViewArn" BudgetDataProperty
-> BudgetDataProperty -> BudgetDataProperty
set PropertyType "BillingViewArn" BudgetDataProperty
newValue BudgetDataProperty {Maybe Object
Maybe (ValueList Text)
Maybe (Value Text)
Maybe CostTypesProperty
Maybe AutoAdjustDataProperty
Maybe SpendProperty
Maybe ExpressionProperty
Maybe TimePeriodProperty
()
Value Text
haddock_workaround_ :: BudgetDataProperty -> ()
autoAdjustData :: BudgetDataProperty -> Maybe AutoAdjustDataProperty
billingViewArn :: BudgetDataProperty -> Maybe (Value Text)
budgetLimit :: BudgetDataProperty -> Maybe SpendProperty
budgetName :: BudgetDataProperty -> Maybe (Value Text)
budgetType :: BudgetDataProperty -> Value Text
costFilters :: BudgetDataProperty -> Maybe Object
costTypes :: BudgetDataProperty -> Maybe CostTypesProperty
filterExpression :: BudgetDataProperty -> Maybe ExpressionProperty
metrics :: BudgetDataProperty -> Maybe (ValueList Text)
plannedBudgetLimits :: BudgetDataProperty -> Maybe Object
timePeriod :: BudgetDataProperty -> Maybe TimePeriodProperty
timeUnit :: BudgetDataProperty -> Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
..}
    = BudgetDataProperty {billingViewArn :: Maybe (Value Text)
billingViewArn = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "BillingViewArn" BudgetDataProperty
Value Text
newValue, Maybe Object
Maybe (ValueList Text)
Maybe (Value Text)
Maybe CostTypesProperty
Maybe AutoAdjustDataProperty
Maybe SpendProperty
Maybe ExpressionProperty
Maybe TimePeriodProperty
()
Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
..}
instance Property "BudgetLimit" BudgetDataProperty where
  type PropertyType "BudgetLimit" BudgetDataProperty = SpendProperty
  set :: PropertyType "BudgetLimit" BudgetDataProperty
-> BudgetDataProperty -> BudgetDataProperty
set PropertyType "BudgetLimit" BudgetDataProperty
newValue BudgetDataProperty {Maybe Object
Maybe (ValueList Text)
Maybe (Value Text)
Maybe CostTypesProperty
Maybe AutoAdjustDataProperty
Maybe SpendProperty
Maybe ExpressionProperty
Maybe TimePeriodProperty
()
Value Text
haddock_workaround_ :: BudgetDataProperty -> ()
autoAdjustData :: BudgetDataProperty -> Maybe AutoAdjustDataProperty
billingViewArn :: BudgetDataProperty -> Maybe (Value Text)
budgetLimit :: BudgetDataProperty -> Maybe SpendProperty
budgetName :: BudgetDataProperty -> Maybe (Value Text)
budgetType :: BudgetDataProperty -> Value Text
costFilters :: BudgetDataProperty -> Maybe Object
costTypes :: BudgetDataProperty -> Maybe CostTypesProperty
filterExpression :: BudgetDataProperty -> Maybe ExpressionProperty
metrics :: BudgetDataProperty -> Maybe (ValueList Text)
plannedBudgetLimits :: BudgetDataProperty -> Maybe Object
timePeriod :: BudgetDataProperty -> Maybe TimePeriodProperty
timeUnit :: BudgetDataProperty -> Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
..}
    = BudgetDataProperty {budgetLimit :: Maybe SpendProperty
budgetLimit = SpendProperty -> Maybe SpendProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "BudgetLimit" BudgetDataProperty
SpendProperty
newValue, Maybe Object
Maybe (ValueList Text)
Maybe (Value Text)
Maybe CostTypesProperty
Maybe AutoAdjustDataProperty
Maybe ExpressionProperty
Maybe TimePeriodProperty
()
Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
..}
instance Property "BudgetName" BudgetDataProperty where
  type PropertyType "BudgetName" BudgetDataProperty = Value Prelude.Text
  set :: PropertyType "BudgetName" BudgetDataProperty
-> BudgetDataProperty -> BudgetDataProperty
set PropertyType "BudgetName" BudgetDataProperty
newValue BudgetDataProperty {Maybe Object
Maybe (ValueList Text)
Maybe (Value Text)
Maybe CostTypesProperty
Maybe AutoAdjustDataProperty
Maybe SpendProperty
Maybe ExpressionProperty
Maybe TimePeriodProperty
()
Value Text
haddock_workaround_ :: BudgetDataProperty -> ()
autoAdjustData :: BudgetDataProperty -> Maybe AutoAdjustDataProperty
billingViewArn :: BudgetDataProperty -> Maybe (Value Text)
budgetLimit :: BudgetDataProperty -> Maybe SpendProperty
budgetName :: BudgetDataProperty -> Maybe (Value Text)
budgetType :: BudgetDataProperty -> Value Text
costFilters :: BudgetDataProperty -> Maybe Object
costTypes :: BudgetDataProperty -> Maybe CostTypesProperty
filterExpression :: BudgetDataProperty -> Maybe ExpressionProperty
metrics :: BudgetDataProperty -> Maybe (ValueList Text)
plannedBudgetLimits :: BudgetDataProperty -> Maybe Object
timePeriod :: BudgetDataProperty -> Maybe TimePeriodProperty
timeUnit :: BudgetDataProperty -> Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
..}
    = BudgetDataProperty {budgetName :: Maybe (Value Text)
budgetName = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "BudgetName" BudgetDataProperty
Value Text
newValue, Maybe Object
Maybe (ValueList Text)
Maybe (Value Text)
Maybe CostTypesProperty
Maybe AutoAdjustDataProperty
Maybe SpendProperty
Maybe ExpressionProperty
Maybe TimePeriodProperty
()
Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
..}
instance Property "BudgetType" BudgetDataProperty where
  type PropertyType "BudgetType" BudgetDataProperty = Value Prelude.Text
  set :: PropertyType "BudgetType" BudgetDataProperty
-> BudgetDataProperty -> BudgetDataProperty
set PropertyType "BudgetType" BudgetDataProperty
newValue BudgetDataProperty {Maybe Object
Maybe (ValueList Text)
Maybe (Value Text)
Maybe CostTypesProperty
Maybe AutoAdjustDataProperty
Maybe SpendProperty
Maybe ExpressionProperty
Maybe TimePeriodProperty
()
Value Text
haddock_workaround_ :: BudgetDataProperty -> ()
autoAdjustData :: BudgetDataProperty -> Maybe AutoAdjustDataProperty
billingViewArn :: BudgetDataProperty -> Maybe (Value Text)
budgetLimit :: BudgetDataProperty -> Maybe SpendProperty
budgetName :: BudgetDataProperty -> Maybe (Value Text)
budgetType :: BudgetDataProperty -> Value Text
costFilters :: BudgetDataProperty -> Maybe Object
costTypes :: BudgetDataProperty -> Maybe CostTypesProperty
filterExpression :: BudgetDataProperty -> Maybe ExpressionProperty
metrics :: BudgetDataProperty -> Maybe (ValueList Text)
plannedBudgetLimits :: BudgetDataProperty -> Maybe Object
timePeriod :: BudgetDataProperty -> Maybe TimePeriodProperty
timeUnit :: BudgetDataProperty -> Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
..}
    = BudgetDataProperty {budgetType :: Value Text
budgetType = PropertyType "BudgetType" BudgetDataProperty
Value Text
newValue, Maybe Object
Maybe (ValueList Text)
Maybe (Value Text)
Maybe CostTypesProperty
Maybe AutoAdjustDataProperty
Maybe SpendProperty
Maybe ExpressionProperty
Maybe TimePeriodProperty
()
Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
..}
instance Property "CostFilters" BudgetDataProperty where
  type PropertyType "CostFilters" BudgetDataProperty = JSON.Object
  set :: PropertyType "CostFilters" BudgetDataProperty
-> BudgetDataProperty -> BudgetDataProperty
set PropertyType "CostFilters" BudgetDataProperty
newValue BudgetDataProperty {Maybe Object
Maybe (ValueList Text)
Maybe (Value Text)
Maybe CostTypesProperty
Maybe AutoAdjustDataProperty
Maybe SpendProperty
Maybe ExpressionProperty
Maybe TimePeriodProperty
()
Value Text
haddock_workaround_ :: BudgetDataProperty -> ()
autoAdjustData :: BudgetDataProperty -> Maybe AutoAdjustDataProperty
billingViewArn :: BudgetDataProperty -> Maybe (Value Text)
budgetLimit :: BudgetDataProperty -> Maybe SpendProperty
budgetName :: BudgetDataProperty -> Maybe (Value Text)
budgetType :: BudgetDataProperty -> Value Text
costFilters :: BudgetDataProperty -> Maybe Object
costTypes :: BudgetDataProperty -> Maybe CostTypesProperty
filterExpression :: BudgetDataProperty -> Maybe ExpressionProperty
metrics :: BudgetDataProperty -> Maybe (ValueList Text)
plannedBudgetLimits :: BudgetDataProperty -> Maybe Object
timePeriod :: BudgetDataProperty -> Maybe TimePeriodProperty
timeUnit :: BudgetDataProperty -> Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
..}
    = BudgetDataProperty {costFilters :: Maybe Object
costFilters = Object -> Maybe Object
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure Object
PropertyType "CostFilters" BudgetDataProperty
newValue, Maybe Object
Maybe (ValueList Text)
Maybe (Value Text)
Maybe CostTypesProperty
Maybe AutoAdjustDataProperty
Maybe SpendProperty
Maybe ExpressionProperty
Maybe TimePeriodProperty
()
Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
..}
instance Property "CostTypes" BudgetDataProperty where
  type PropertyType "CostTypes" BudgetDataProperty = CostTypesProperty
  set :: PropertyType "CostTypes" BudgetDataProperty
-> BudgetDataProperty -> BudgetDataProperty
set PropertyType "CostTypes" BudgetDataProperty
newValue BudgetDataProperty {Maybe Object
Maybe (ValueList Text)
Maybe (Value Text)
Maybe CostTypesProperty
Maybe AutoAdjustDataProperty
Maybe SpendProperty
Maybe ExpressionProperty
Maybe TimePeriodProperty
()
Value Text
haddock_workaround_ :: BudgetDataProperty -> ()
autoAdjustData :: BudgetDataProperty -> Maybe AutoAdjustDataProperty
billingViewArn :: BudgetDataProperty -> Maybe (Value Text)
budgetLimit :: BudgetDataProperty -> Maybe SpendProperty
budgetName :: BudgetDataProperty -> Maybe (Value Text)
budgetType :: BudgetDataProperty -> Value Text
costFilters :: BudgetDataProperty -> Maybe Object
costTypes :: BudgetDataProperty -> Maybe CostTypesProperty
filterExpression :: BudgetDataProperty -> Maybe ExpressionProperty
metrics :: BudgetDataProperty -> Maybe (ValueList Text)
plannedBudgetLimits :: BudgetDataProperty -> Maybe Object
timePeriod :: BudgetDataProperty -> Maybe TimePeriodProperty
timeUnit :: BudgetDataProperty -> Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
..}
    = BudgetDataProperty {costTypes :: Maybe CostTypesProperty
costTypes = CostTypesProperty -> Maybe CostTypesProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "CostTypes" BudgetDataProperty
CostTypesProperty
newValue, Maybe Object
Maybe (ValueList Text)
Maybe (Value Text)
Maybe AutoAdjustDataProperty
Maybe SpendProperty
Maybe ExpressionProperty
Maybe TimePeriodProperty
()
Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
..}
instance Property "FilterExpression" BudgetDataProperty where
  type PropertyType "FilterExpression" BudgetDataProperty = ExpressionProperty
  set :: PropertyType "FilterExpression" BudgetDataProperty
-> BudgetDataProperty -> BudgetDataProperty
set PropertyType "FilterExpression" BudgetDataProperty
newValue BudgetDataProperty {Maybe Object
Maybe (ValueList Text)
Maybe (Value Text)
Maybe CostTypesProperty
Maybe AutoAdjustDataProperty
Maybe SpendProperty
Maybe ExpressionProperty
Maybe TimePeriodProperty
()
Value Text
haddock_workaround_ :: BudgetDataProperty -> ()
autoAdjustData :: BudgetDataProperty -> Maybe AutoAdjustDataProperty
billingViewArn :: BudgetDataProperty -> Maybe (Value Text)
budgetLimit :: BudgetDataProperty -> Maybe SpendProperty
budgetName :: BudgetDataProperty -> Maybe (Value Text)
budgetType :: BudgetDataProperty -> Value Text
costFilters :: BudgetDataProperty -> Maybe Object
costTypes :: BudgetDataProperty -> Maybe CostTypesProperty
filterExpression :: BudgetDataProperty -> Maybe ExpressionProperty
metrics :: BudgetDataProperty -> Maybe (ValueList Text)
plannedBudgetLimits :: BudgetDataProperty -> Maybe Object
timePeriod :: BudgetDataProperty -> Maybe TimePeriodProperty
timeUnit :: BudgetDataProperty -> Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
..}
    = BudgetDataProperty {filterExpression :: Maybe ExpressionProperty
filterExpression = ExpressionProperty -> Maybe ExpressionProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "FilterExpression" BudgetDataProperty
ExpressionProperty
newValue, Maybe Object
Maybe (ValueList Text)
Maybe (Value Text)
Maybe CostTypesProperty
Maybe AutoAdjustDataProperty
Maybe SpendProperty
Maybe TimePeriodProperty
()
Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
..}
instance Property "Metrics" BudgetDataProperty where
  type PropertyType "Metrics" BudgetDataProperty = ValueList Prelude.Text
  set :: PropertyType "Metrics" BudgetDataProperty
-> BudgetDataProperty -> BudgetDataProperty
set PropertyType "Metrics" BudgetDataProperty
newValue BudgetDataProperty {Maybe Object
Maybe (ValueList Text)
Maybe (Value Text)
Maybe CostTypesProperty
Maybe AutoAdjustDataProperty
Maybe SpendProperty
Maybe ExpressionProperty
Maybe TimePeriodProperty
()
Value Text
haddock_workaround_ :: BudgetDataProperty -> ()
autoAdjustData :: BudgetDataProperty -> Maybe AutoAdjustDataProperty
billingViewArn :: BudgetDataProperty -> Maybe (Value Text)
budgetLimit :: BudgetDataProperty -> Maybe SpendProperty
budgetName :: BudgetDataProperty -> Maybe (Value Text)
budgetType :: BudgetDataProperty -> Value Text
costFilters :: BudgetDataProperty -> Maybe Object
costTypes :: BudgetDataProperty -> Maybe CostTypesProperty
filterExpression :: BudgetDataProperty -> Maybe ExpressionProperty
metrics :: BudgetDataProperty -> Maybe (ValueList Text)
plannedBudgetLimits :: BudgetDataProperty -> Maybe Object
timePeriod :: BudgetDataProperty -> Maybe TimePeriodProperty
timeUnit :: BudgetDataProperty -> Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
..}
    = BudgetDataProperty {metrics :: Maybe (ValueList Text)
metrics = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Metrics" BudgetDataProperty
ValueList Text
newValue, Maybe Object
Maybe (Value Text)
Maybe CostTypesProperty
Maybe AutoAdjustDataProperty
Maybe SpendProperty
Maybe ExpressionProperty
Maybe TimePeriodProperty
()
Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
..}
instance Property "PlannedBudgetLimits" BudgetDataProperty where
  type PropertyType "PlannedBudgetLimits" BudgetDataProperty = JSON.Object
  set :: PropertyType "PlannedBudgetLimits" BudgetDataProperty
-> BudgetDataProperty -> BudgetDataProperty
set PropertyType "PlannedBudgetLimits" BudgetDataProperty
newValue BudgetDataProperty {Maybe Object
Maybe (ValueList Text)
Maybe (Value Text)
Maybe CostTypesProperty
Maybe AutoAdjustDataProperty
Maybe SpendProperty
Maybe ExpressionProperty
Maybe TimePeriodProperty
()
Value Text
haddock_workaround_ :: BudgetDataProperty -> ()
autoAdjustData :: BudgetDataProperty -> Maybe AutoAdjustDataProperty
billingViewArn :: BudgetDataProperty -> Maybe (Value Text)
budgetLimit :: BudgetDataProperty -> Maybe SpendProperty
budgetName :: BudgetDataProperty -> Maybe (Value Text)
budgetType :: BudgetDataProperty -> Value Text
costFilters :: BudgetDataProperty -> Maybe Object
costTypes :: BudgetDataProperty -> Maybe CostTypesProperty
filterExpression :: BudgetDataProperty -> Maybe ExpressionProperty
metrics :: BudgetDataProperty -> Maybe (ValueList Text)
plannedBudgetLimits :: BudgetDataProperty -> Maybe Object
timePeriod :: BudgetDataProperty -> Maybe TimePeriodProperty
timeUnit :: BudgetDataProperty -> Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
..}
    = BudgetDataProperty
        {plannedBudgetLimits :: Maybe Object
plannedBudgetLimits = Object -> Maybe Object
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure Object
PropertyType "PlannedBudgetLimits" BudgetDataProperty
newValue, Maybe Object
Maybe (ValueList Text)
Maybe (Value Text)
Maybe CostTypesProperty
Maybe AutoAdjustDataProperty
Maybe SpendProperty
Maybe ExpressionProperty
Maybe TimePeriodProperty
()
Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
..}
instance Property "TimePeriod" BudgetDataProperty where
  type PropertyType "TimePeriod" BudgetDataProperty = TimePeriodProperty
  set :: PropertyType "TimePeriod" BudgetDataProperty
-> BudgetDataProperty -> BudgetDataProperty
set PropertyType "TimePeriod" BudgetDataProperty
newValue BudgetDataProperty {Maybe Object
Maybe (ValueList Text)
Maybe (Value Text)
Maybe CostTypesProperty
Maybe AutoAdjustDataProperty
Maybe SpendProperty
Maybe ExpressionProperty
Maybe TimePeriodProperty
()
Value Text
haddock_workaround_ :: BudgetDataProperty -> ()
autoAdjustData :: BudgetDataProperty -> Maybe AutoAdjustDataProperty
billingViewArn :: BudgetDataProperty -> Maybe (Value Text)
budgetLimit :: BudgetDataProperty -> Maybe SpendProperty
budgetName :: BudgetDataProperty -> Maybe (Value Text)
budgetType :: BudgetDataProperty -> Value Text
costFilters :: BudgetDataProperty -> Maybe Object
costTypes :: BudgetDataProperty -> Maybe CostTypesProperty
filterExpression :: BudgetDataProperty -> Maybe ExpressionProperty
metrics :: BudgetDataProperty -> Maybe (ValueList Text)
plannedBudgetLimits :: BudgetDataProperty -> Maybe Object
timePeriod :: BudgetDataProperty -> Maybe TimePeriodProperty
timeUnit :: BudgetDataProperty -> Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
..}
    = BudgetDataProperty {timePeriod :: Maybe TimePeriodProperty
timePeriod = TimePeriodProperty -> Maybe TimePeriodProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "TimePeriod" BudgetDataProperty
TimePeriodProperty
newValue, Maybe Object
Maybe (ValueList Text)
Maybe (Value Text)
Maybe CostTypesProperty
Maybe AutoAdjustDataProperty
Maybe SpendProperty
Maybe ExpressionProperty
()
Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timeUnit :: Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timeUnit :: Value Text
..}
instance Property "TimeUnit" BudgetDataProperty where
  type PropertyType "TimeUnit" BudgetDataProperty = Value Prelude.Text
  set :: PropertyType "TimeUnit" BudgetDataProperty
-> BudgetDataProperty -> BudgetDataProperty
set PropertyType "TimeUnit" BudgetDataProperty
newValue BudgetDataProperty {Maybe Object
Maybe (ValueList Text)
Maybe (Value Text)
Maybe CostTypesProperty
Maybe AutoAdjustDataProperty
Maybe SpendProperty
Maybe ExpressionProperty
Maybe TimePeriodProperty
()
Value Text
haddock_workaround_ :: BudgetDataProperty -> ()
autoAdjustData :: BudgetDataProperty -> Maybe AutoAdjustDataProperty
billingViewArn :: BudgetDataProperty -> Maybe (Value Text)
budgetLimit :: BudgetDataProperty -> Maybe SpendProperty
budgetName :: BudgetDataProperty -> Maybe (Value Text)
budgetType :: BudgetDataProperty -> Value Text
costFilters :: BudgetDataProperty -> Maybe Object
costTypes :: BudgetDataProperty -> Maybe CostTypesProperty
filterExpression :: BudgetDataProperty -> Maybe ExpressionProperty
metrics :: BudgetDataProperty -> Maybe (ValueList Text)
plannedBudgetLimits :: BudgetDataProperty -> Maybe Object
timePeriod :: BudgetDataProperty -> Maybe TimePeriodProperty
timeUnit :: BudgetDataProperty -> Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
timeUnit :: Value Text
..}
    = BudgetDataProperty {timeUnit :: Value Text
timeUnit = PropertyType "TimeUnit" BudgetDataProperty
Value Text
newValue, Maybe Object
Maybe (ValueList Text)
Maybe (Value Text)
Maybe CostTypesProperty
Maybe AutoAdjustDataProperty
Maybe SpendProperty
Maybe ExpressionProperty
Maybe TimePeriodProperty
()
Value Text
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
haddock_workaround_ :: ()
autoAdjustData :: Maybe AutoAdjustDataProperty
billingViewArn :: Maybe (Value Text)
budgetLimit :: Maybe SpendProperty
budgetName :: Maybe (Value Text)
budgetType :: Value Text
costFilters :: Maybe Object
costTypes :: Maybe CostTypesProperty
filterExpression :: Maybe ExpressionProperty
metrics :: Maybe (ValueList Text)
plannedBudgetLimits :: Maybe Object
timePeriod :: Maybe TimePeriodProperty
..}