amazonka-budgets-1.5.0: Amazon Budgets SDK.

Copyright(c) 2013-2017 Brendan Hay
LicenseMozilla Public License, v. 2.0.
MaintainerBrendan Hay <brendan.g.hay+amazonka@gmail.com>
Stabilityauto-generated
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Network.AWS.Budgets.Types

Contents

Description

 

Synopsis

Service Configuration

budgets :: Service Source #

API version 2016-10-20 of the Amazon Budgets SDK configuration.

Errors

_InvalidParameterException :: AsError a => Getting (First ServiceError) a ServiceError Source #

This exception is thrown if any request is given an invalid parameter. E.g., if a required Date field is null.

_InternalErrorException :: AsError a => Getting (First ServiceError) a ServiceError Source #

This exception is thrown on an unknown internal failure.

_ExpiredNextTokenException :: AsError a => Getting (First ServiceError) a ServiceError Source #

This exception is thrown if the paging token is expired - past its TTL

_NotFoundException :: AsError a => Getting (First ServiceError) a ServiceError Source #

This exception is thrown if a requested entity is not found. E.g., if a budget id doesn't exist for an account ID.

_InvalidNextTokenException :: AsError a => Getting (First ServiceError) a ServiceError Source #

This exception is thrown if paging token signature didn't match the token, or the paging token isn't for this request

_DuplicateRecordException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The exception is thrown when customer tries to create a record (e.g. budget) that already exists.

_CreationLimitExceededException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The exception is thrown when customer tries to create a record (e.g. budget), but the number this record already exceeds the limitation.

BudgetType

data BudgetType Source #

The type of a budget. It should be COST, USAGE, or RI_UTILIZATION.

Constructors

Cost 
RiUtilization 
Usage 

Instances

Bounded BudgetType Source # 
Enum BudgetType Source # 
Eq BudgetType Source # 
Data BudgetType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BudgetType -> c BudgetType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BudgetType #

toConstr :: BudgetType -> Constr #

dataTypeOf :: BudgetType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BudgetType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BudgetType) #

gmapT :: (forall b. Data b => b -> b) -> BudgetType -> BudgetType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BudgetType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BudgetType -> r #

gmapQ :: (forall d. Data d => d -> u) -> BudgetType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BudgetType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BudgetType -> m BudgetType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BudgetType -> m BudgetType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BudgetType -> m BudgetType #

Ord BudgetType Source # 
Read BudgetType Source # 
Show BudgetType Source # 
Generic BudgetType Source # 

Associated Types

type Rep BudgetType :: * -> * #

Hashable BudgetType Source # 
FromJSON BudgetType Source # 
ToJSON BudgetType Source # 
NFData BudgetType Source # 

Methods

rnf :: BudgetType -> () #

ToQuery BudgetType Source # 
ToHeader BudgetType Source # 
ToByteString BudgetType Source # 
FromText BudgetType Source # 
ToText BudgetType Source # 

Methods

toText :: BudgetType -> Text #

type Rep BudgetType Source # 
type Rep BudgetType = D1 (MetaData "BudgetType" "Network.AWS.Budgets.Types.Sum" "amazonka-budgets-1.5.0-DxVvOYx4s4rzRpD440Wv4" False) ((:+:) (C1 (MetaCons "Cost" PrefixI False) U1) ((:+:) (C1 (MetaCons "RiUtilization" PrefixI False) U1) (C1 (MetaCons "Usage" PrefixI False) U1)))

ComparisonOperator

data ComparisonOperator Source #

The comparison operator of a notification. Currently we support less than, equal to and greater than.

Constructors

EqualTo 
GreaterThan 
LessThan 

Instances

Bounded ComparisonOperator Source # 
Enum ComparisonOperator Source # 
Eq ComparisonOperator Source # 
Data ComparisonOperator Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ComparisonOperator -> c ComparisonOperator #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ComparisonOperator #

toConstr :: ComparisonOperator -> Constr #

dataTypeOf :: ComparisonOperator -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ComparisonOperator) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ComparisonOperator) #

gmapT :: (forall b. Data b => b -> b) -> ComparisonOperator -> ComparisonOperator #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ComparisonOperator -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ComparisonOperator -> r #

gmapQ :: (forall d. Data d => d -> u) -> ComparisonOperator -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ComparisonOperator -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ComparisonOperator -> m ComparisonOperator #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ComparisonOperator -> m ComparisonOperator #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ComparisonOperator -> m ComparisonOperator #

Ord ComparisonOperator Source # 
Read ComparisonOperator Source # 
Show ComparisonOperator Source # 
Generic ComparisonOperator Source # 
Hashable ComparisonOperator Source # 
FromJSON ComparisonOperator Source # 
ToJSON ComparisonOperator Source # 
NFData ComparisonOperator Source # 

Methods

rnf :: ComparisonOperator -> () #

ToQuery ComparisonOperator Source # 
ToHeader ComparisonOperator Source # 
ToByteString ComparisonOperator Source # 
FromText ComparisonOperator Source # 
ToText ComparisonOperator Source # 
type Rep ComparisonOperator Source # 
type Rep ComparisonOperator = D1 (MetaData "ComparisonOperator" "Network.AWS.Budgets.Types.Sum" "amazonka-budgets-1.5.0-DxVvOYx4s4rzRpD440Wv4" False) ((:+:) (C1 (MetaCons "EqualTo" PrefixI False) U1) ((:+:) (C1 (MetaCons "GreaterThan" PrefixI False) U1) (C1 (MetaCons "LessThan" PrefixI False) U1)))

NotificationType

data NotificationType Source #

The type of a notification. It should be ACTUAL or FORECASTED.

Constructors

Actual 
Forecasted 

Instances

Bounded NotificationType Source # 
Enum NotificationType Source # 
Eq NotificationType Source # 
Data NotificationType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NotificationType -> c NotificationType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NotificationType #

toConstr :: NotificationType -> Constr #

dataTypeOf :: NotificationType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c NotificationType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NotificationType) #

gmapT :: (forall b. Data b => b -> b) -> NotificationType -> NotificationType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NotificationType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NotificationType -> r #

gmapQ :: (forall d. Data d => d -> u) -> NotificationType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NotificationType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NotificationType -> m NotificationType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NotificationType -> m NotificationType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NotificationType -> m NotificationType #

Ord NotificationType Source # 
Read NotificationType Source # 
Show NotificationType Source # 
Generic NotificationType Source # 
Hashable NotificationType Source # 
FromJSON NotificationType Source # 
ToJSON NotificationType Source # 
NFData NotificationType Source # 

Methods

rnf :: NotificationType -> () #

ToQuery NotificationType Source # 
ToHeader NotificationType Source # 
ToByteString NotificationType Source # 
FromText NotificationType Source # 
ToText NotificationType Source # 
type Rep NotificationType Source # 
type Rep NotificationType = D1 (MetaData "NotificationType" "Network.AWS.Budgets.Types.Sum" "amazonka-budgets-1.5.0-DxVvOYx4s4rzRpD440Wv4" False) ((:+:) (C1 (MetaCons "Actual" PrefixI False) U1) (C1 (MetaCons "Forecasted" PrefixI False) U1))

SubscriptionType

data SubscriptionType Source #

The subscription type of the subscriber. It can be SMS or EMAIL.

Constructors

Email 
SNS 

Instances

Bounded SubscriptionType Source # 
Enum SubscriptionType Source # 
Eq SubscriptionType Source # 
Data SubscriptionType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SubscriptionType -> c SubscriptionType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SubscriptionType #

toConstr :: SubscriptionType -> Constr #

dataTypeOf :: SubscriptionType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SubscriptionType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SubscriptionType) #

gmapT :: (forall b. Data b => b -> b) -> SubscriptionType -> SubscriptionType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SubscriptionType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SubscriptionType -> r #

gmapQ :: (forall d. Data d => d -> u) -> SubscriptionType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SubscriptionType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SubscriptionType -> m SubscriptionType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SubscriptionType -> m SubscriptionType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SubscriptionType -> m SubscriptionType #

Ord SubscriptionType Source # 
Read SubscriptionType Source # 
Show SubscriptionType Source # 
Generic SubscriptionType Source # 
Hashable SubscriptionType Source # 
FromJSON SubscriptionType Source # 
ToJSON SubscriptionType Source # 
NFData SubscriptionType Source # 

Methods

rnf :: SubscriptionType -> () #

ToQuery SubscriptionType Source # 
ToHeader SubscriptionType Source # 
ToByteString SubscriptionType Source # 
FromText SubscriptionType Source # 
ToText SubscriptionType Source # 
type Rep SubscriptionType Source # 
type Rep SubscriptionType = D1 (MetaData "SubscriptionType" "Network.AWS.Budgets.Types.Sum" "amazonka-budgets-1.5.0-DxVvOYx4s4rzRpD440Wv4" False) ((:+:) (C1 (MetaCons "Email" PrefixI False) U1) (C1 (MetaCons "SNS" PrefixI False) U1))

ThresholdType

data ThresholdType Source #

The type of threshold for a notification. It can be PERCENTAGE or ABSOLUTE_VALUE.

Constructors

AbsoluteValue 
Percentage 

Instances

Bounded ThresholdType Source # 
Enum ThresholdType Source # 
Eq ThresholdType Source # 
Data ThresholdType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ThresholdType -> c ThresholdType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ThresholdType #

toConstr :: ThresholdType -> Constr #

dataTypeOf :: ThresholdType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ThresholdType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ThresholdType) #

gmapT :: (forall b. Data b => b -> b) -> ThresholdType -> ThresholdType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ThresholdType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ThresholdType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ThresholdType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ThresholdType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ThresholdType -> m ThresholdType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ThresholdType -> m ThresholdType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ThresholdType -> m ThresholdType #

Ord ThresholdType Source # 
Read ThresholdType Source # 
Show ThresholdType Source # 
Generic ThresholdType Source # 

Associated Types

type Rep ThresholdType :: * -> * #

Hashable ThresholdType Source # 
FromJSON ThresholdType Source # 
ToJSON ThresholdType Source # 
NFData ThresholdType Source # 

Methods

rnf :: ThresholdType -> () #

ToQuery ThresholdType Source # 
ToHeader ThresholdType Source # 
ToByteString ThresholdType Source # 
FromText ThresholdType Source # 
ToText ThresholdType Source # 

Methods

toText :: ThresholdType -> Text #

type Rep ThresholdType Source # 
type Rep ThresholdType = D1 (MetaData "ThresholdType" "Network.AWS.Budgets.Types.Sum" "amazonka-budgets-1.5.0-DxVvOYx4s4rzRpD440Wv4" False) ((:+:) (C1 (MetaCons "AbsoluteValue" PrefixI False) U1) (C1 (MetaCons "Percentage" PrefixI False) U1))

TimeUnit

data TimeUnit Source #

The time unit of the budget. e.g. MONTHLY, QUARTERLY, etc.

Constructors

Annually 
Daily 
Monthly 
Quarterly 

Instances

Bounded TimeUnit Source # 
Enum TimeUnit Source # 
Eq TimeUnit Source # 
Data TimeUnit Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TimeUnit -> c TimeUnit #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TimeUnit #

toConstr :: TimeUnit -> Constr #

dataTypeOf :: TimeUnit -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TimeUnit) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimeUnit) #

gmapT :: (forall b. Data b => b -> b) -> TimeUnit -> TimeUnit #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TimeUnit -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TimeUnit -> r #

gmapQ :: (forall d. Data d => d -> u) -> TimeUnit -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TimeUnit -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TimeUnit -> m TimeUnit #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeUnit -> m TimeUnit #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeUnit -> m TimeUnit #

Ord TimeUnit Source # 
Read TimeUnit Source # 
Show TimeUnit Source # 
Generic TimeUnit Source # 

Associated Types

type Rep TimeUnit :: * -> * #

Methods

from :: TimeUnit -> Rep TimeUnit x #

to :: Rep TimeUnit x -> TimeUnit #

Hashable TimeUnit Source # 

Methods

hashWithSalt :: Int -> TimeUnit -> Int #

hash :: TimeUnit -> Int #

FromJSON TimeUnit Source # 
ToJSON TimeUnit Source # 
NFData TimeUnit Source # 

Methods

rnf :: TimeUnit -> () #

ToQuery TimeUnit Source # 
ToHeader TimeUnit Source # 

Methods

toHeader :: HeaderName -> TimeUnit -> [Header] #

ToByteString TimeUnit Source # 

Methods

toBS :: TimeUnit -> ByteString #

FromText TimeUnit Source # 
ToText TimeUnit Source # 

Methods

toText :: TimeUnit -> Text #

type Rep TimeUnit Source # 
type Rep TimeUnit = D1 (MetaData "TimeUnit" "Network.AWS.Budgets.Types.Sum" "amazonka-budgets-1.5.0-DxVvOYx4s4rzRpD440Wv4" False) ((:+:) ((:+:) (C1 (MetaCons "Annually" PrefixI False) U1) (C1 (MetaCons "Daily" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Monthly" PrefixI False) U1) (C1 (MetaCons "Quarterly" PrefixI False) U1)))

Budget

data Budget Source #

AWS Budget model

See: budget smart constructor.

Instances

Eq Budget Source # 

Methods

(==) :: Budget -> Budget -> Bool #

(/=) :: Budget -> Budget -> Bool #

Data Budget Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Budget -> c Budget #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Budget #

toConstr :: Budget -> Constr #

dataTypeOf :: Budget -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Budget) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Budget) #

gmapT :: (forall b. Data b => b -> b) -> Budget -> Budget #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Budget -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Budget -> r #

gmapQ :: (forall d. Data d => d -> u) -> Budget -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Budget -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Budget -> m Budget #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Budget -> m Budget #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Budget -> m Budget #

Read Budget Source # 
Show Budget Source # 
Generic Budget Source # 

Associated Types

type Rep Budget :: * -> * #

Methods

from :: Budget -> Rep Budget x #

to :: Rep Budget x -> Budget #

Hashable Budget Source # 

Methods

hashWithSalt :: Int -> Budget -> Int #

hash :: Budget -> Int #

FromJSON Budget Source # 
ToJSON Budget Source # 
NFData Budget Source # 

Methods

rnf :: Budget -> () #

type Rep Budget Source # 

budget Source #

Creates a value of Budget with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

bCostFilters :: Lens' Budget (HashMap Text [Text]) Source #

Undocumented member.

bBudgetName :: Lens' Budget Text Source #

Undocumented member.

bBudgetLimit :: Lens' Budget Spend Source #

Undocumented member.

bCostTypes :: Lens' Budget CostTypes Source #

Undocumented member.

bTimeUnit :: Lens' Budget TimeUnit Source #

Undocumented member.

bTimePeriod :: Lens' Budget TimePeriod Source #

Undocumented member.

bBudgetType :: Lens' Budget BudgetType Source #

Undocumented member.

CalculatedSpend

data CalculatedSpend Source #

A structure that holds the actual and forecasted spend for a budget.

See: calculatedSpend smart constructor.

Instances

Eq CalculatedSpend Source # 
Data CalculatedSpend Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CalculatedSpend -> c CalculatedSpend #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CalculatedSpend #

toConstr :: CalculatedSpend -> Constr #

dataTypeOf :: CalculatedSpend -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CalculatedSpend) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CalculatedSpend) #

gmapT :: (forall b. Data b => b -> b) -> CalculatedSpend -> CalculatedSpend #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CalculatedSpend -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CalculatedSpend -> r #

gmapQ :: (forall d. Data d => d -> u) -> CalculatedSpend -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CalculatedSpend -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CalculatedSpend -> m CalculatedSpend #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CalculatedSpend -> m CalculatedSpend #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CalculatedSpend -> m CalculatedSpend #

Read CalculatedSpend Source # 
Show CalculatedSpend Source # 
Generic CalculatedSpend Source # 
Hashable CalculatedSpend Source # 
FromJSON CalculatedSpend Source # 
ToJSON CalculatedSpend Source # 
NFData CalculatedSpend Source # 

Methods

rnf :: CalculatedSpend -> () #

type Rep CalculatedSpend Source # 
type Rep CalculatedSpend = D1 (MetaData "CalculatedSpend" "Network.AWS.Budgets.Types.Product" "amazonka-budgets-1.5.0-DxVvOYx4s4rzRpD440Wv4" False) (C1 (MetaCons "CalculatedSpend'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_csForecastedSpend") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Spend))) (S1 (MetaSel (Just Symbol "_csActualSpend") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Spend))))

calculatedSpend Source #

Creates a value of CalculatedSpend with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

CostTypes

data CostTypes Source #

This includes the options for getting the cost of a budget.

See: costTypes smart constructor.

Instances

Eq CostTypes Source # 
Data CostTypes Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CostTypes -> c CostTypes #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CostTypes #

toConstr :: CostTypes -> Constr #

dataTypeOf :: CostTypes -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CostTypes) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CostTypes) #

gmapT :: (forall b. Data b => b -> b) -> CostTypes -> CostTypes #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CostTypes -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CostTypes -> r #

gmapQ :: (forall d. Data d => d -> u) -> CostTypes -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CostTypes -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CostTypes -> m CostTypes #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CostTypes -> m CostTypes #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CostTypes -> m CostTypes #

Read CostTypes Source # 
Show CostTypes Source # 
Generic CostTypes Source # 

Associated Types

type Rep CostTypes :: * -> * #

Hashable CostTypes Source # 
FromJSON CostTypes Source # 
ToJSON CostTypes Source # 
NFData CostTypes Source # 

Methods

rnf :: CostTypes -> () #

type Rep CostTypes Source # 
type Rep CostTypes = D1 (MetaData "CostTypes" "Network.AWS.Budgets.Types.Product" "amazonka-budgets-1.5.0-DxVvOYx4s4rzRpD440Wv4" False) (C1 (MetaCons "CostTypes'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ctIncludeTax") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool)) ((:*:) (S1 (MetaSel (Just Symbol "_ctIncludeSubscription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "_ctUseBlended") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool)))))

costTypes Source #

Creates a value of CostTypes with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ctIncludeTax :: Lens' CostTypes Bool Source #

Undocumented member.

ctUseBlended :: Lens' CostTypes Bool Source #

Undocumented member.

Notification

data Notification Source #

Notification model. Each budget may contain multiple notifications with different settings.

See: notification smart constructor.

Instances

Eq Notification Source # 
Data Notification Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Notification -> c Notification #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Notification #

toConstr :: Notification -> Constr #

dataTypeOf :: Notification -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Notification) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Notification) #

gmapT :: (forall b. Data b => b -> b) -> Notification -> Notification #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Notification -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Notification -> r #

gmapQ :: (forall d. Data d => d -> u) -> Notification -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Notification -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Notification -> m Notification #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Notification -> m Notification #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Notification -> m Notification #

Read Notification Source # 
Show Notification Source # 
Generic Notification Source # 

Associated Types

type Rep Notification :: * -> * #

Hashable Notification Source # 
FromJSON Notification Source # 
ToJSON Notification Source # 
NFData Notification Source # 

Methods

rnf :: Notification -> () #

type Rep Notification Source # 
type Rep Notification = D1 (MetaData "Notification" "Network.AWS.Budgets.Types.Product" "amazonka-budgets-1.5.0-DxVvOYx4s4rzRpD440Wv4" False) (C1 (MetaCons "Notification'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_nThresholdType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ThresholdType))) (S1 (MetaSel (Just Symbol "_nNotificationType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 NotificationType))) ((:*:) (S1 (MetaSel (Just Symbol "_nComparisonOperator") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ComparisonOperator)) (S1 (MetaSel (Just Symbol "_nThreshold") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)))))

notification Source #

Creates a value of Notification with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

nThreshold :: Lens' Notification Double Source #

Undocumented member.

NotificationWithSubscribers

data NotificationWithSubscribers Source #

A structure to relate notification and a list of subscribers who belong to the notification.

See: notificationWithSubscribers smart constructor.

Instances

Eq NotificationWithSubscribers Source # 
Data NotificationWithSubscribers Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NotificationWithSubscribers -> c NotificationWithSubscribers #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NotificationWithSubscribers #

toConstr :: NotificationWithSubscribers -> Constr #

dataTypeOf :: NotificationWithSubscribers -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c NotificationWithSubscribers) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NotificationWithSubscribers) #

gmapT :: (forall b. Data b => b -> b) -> NotificationWithSubscribers -> NotificationWithSubscribers #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NotificationWithSubscribers -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NotificationWithSubscribers -> r #

gmapQ :: (forall d. Data d => d -> u) -> NotificationWithSubscribers -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NotificationWithSubscribers -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NotificationWithSubscribers -> m NotificationWithSubscribers #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NotificationWithSubscribers -> m NotificationWithSubscribers #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NotificationWithSubscribers -> m NotificationWithSubscribers #

Read NotificationWithSubscribers Source # 
Show NotificationWithSubscribers Source # 
Generic NotificationWithSubscribers Source # 
Hashable NotificationWithSubscribers Source # 
ToJSON NotificationWithSubscribers Source # 
NFData NotificationWithSubscribers Source # 
type Rep NotificationWithSubscribers Source # 
type Rep NotificationWithSubscribers = D1 (MetaData "NotificationWithSubscribers" "Network.AWS.Budgets.Types.Product" "amazonka-budgets-1.5.0-DxVvOYx4s4rzRpD440Wv4" False) (C1 (MetaCons "NotificationWithSubscribers'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_nwsNotification") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Notification)) (S1 (MetaSel (Just Symbol "_nwsSubscribers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (List1 Subscriber)))))

notificationWithSubscribers Source #

Creates a value of NotificationWithSubscribers with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

Spend

data Spend Source #

A structure that represents either a cost spend or usage spend. Contains an amount and a unit.

See: spend smart constructor.

Instances

Eq Spend Source # 

Methods

(==) :: Spend -> Spend -> Bool #

(/=) :: Spend -> Spend -> Bool #

Data Spend Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Spend -> c Spend #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Spend #

toConstr :: Spend -> Constr #

dataTypeOf :: Spend -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Spend) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Spend) #

gmapT :: (forall b. Data b => b -> b) -> Spend -> Spend #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Spend -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Spend -> r #

gmapQ :: (forall d. Data d => d -> u) -> Spend -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Spend -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Spend -> m Spend #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Spend -> m Spend #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Spend -> m Spend #

Read Spend Source # 
Show Spend Source # 

Methods

showsPrec :: Int -> Spend -> ShowS #

show :: Spend -> String #

showList :: [Spend] -> ShowS #

Generic Spend Source # 

Associated Types

type Rep Spend :: * -> * #

Methods

from :: Spend -> Rep Spend x #

to :: Rep Spend x -> Spend #

Hashable Spend Source # 

Methods

hashWithSalt :: Int -> Spend -> Int #

hash :: Spend -> Int #

FromJSON Spend Source # 
ToJSON Spend Source # 
NFData Spend Source # 

Methods

rnf :: Spend -> () #

type Rep Spend Source # 
type Rep Spend = D1 (MetaData "Spend" "Network.AWS.Budgets.Types.Product" "amazonka-budgets-1.5.0-DxVvOYx4s4rzRpD440Wv4" False) (C1 (MetaCons "Spend'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_sAmount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_sUnit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

spend Source #

Arguments

:: Text

sAmount

-> Text

sUnit

-> Spend 

Creates a value of Spend with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

sAmount :: Lens' Spend Text Source #

Undocumented member.

sUnit :: Lens' Spend Text Source #

Undocumented member.

Subscriber

data Subscriber Source #

Subscriber model. Each notification may contain multiple subscribers with different addresses.

See: subscriber smart constructor.

Instances

Eq Subscriber Source # 
Data Subscriber Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Subscriber -> c Subscriber #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Subscriber #

toConstr :: Subscriber -> Constr #

dataTypeOf :: Subscriber -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Subscriber) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Subscriber) #

gmapT :: (forall b. Data b => b -> b) -> Subscriber -> Subscriber #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Subscriber -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Subscriber -> r #

gmapQ :: (forall d. Data d => d -> u) -> Subscriber -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Subscriber -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Subscriber -> m Subscriber #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Subscriber -> m Subscriber #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Subscriber -> m Subscriber #

Read Subscriber Source # 
Show Subscriber Source # 
Generic Subscriber Source # 

Associated Types

type Rep Subscriber :: * -> * #

Hashable Subscriber Source # 
FromJSON Subscriber Source # 
ToJSON Subscriber Source # 
NFData Subscriber Source # 

Methods

rnf :: Subscriber -> () #

type Rep Subscriber Source # 
type Rep Subscriber = D1 (MetaData "Subscriber" "Network.AWS.Budgets.Types.Product" "amazonka-budgets-1.5.0-DxVvOYx4s4rzRpD440Wv4" False) (C1 (MetaCons "Subscriber'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_sSubscriptionType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SubscriptionType)) (S1 (MetaSel (Just Symbol "_sAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

subscriber Source #

Creates a value of Subscriber with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

sAddress :: Lens' Subscriber Text Source #

Undocumented member.

TimePeriod

data TimePeriod Source #

A time period indicating the start date and end date of a budget.

See: timePeriod smart constructor.

Instances

Eq TimePeriod Source # 
Data TimePeriod Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TimePeriod -> c TimePeriod #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TimePeriod #

toConstr :: TimePeriod -> Constr #

dataTypeOf :: TimePeriod -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TimePeriod) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimePeriod) #

gmapT :: (forall b. Data b => b -> b) -> TimePeriod -> TimePeriod #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TimePeriod -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TimePeriod -> r #

gmapQ :: (forall d. Data d => d -> u) -> TimePeriod -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TimePeriod -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TimePeriod -> m TimePeriod #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TimePeriod -> m TimePeriod #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TimePeriod -> m TimePeriod #

Read TimePeriod Source # 
Show TimePeriod Source # 
Generic TimePeriod Source # 

Associated Types

type Rep TimePeriod :: * -> * #

Hashable TimePeriod Source # 
FromJSON TimePeriod Source # 
ToJSON TimePeriod Source # 
NFData TimePeriod Source # 

Methods

rnf :: TimePeriod -> () #

type Rep TimePeriod Source # 
type Rep TimePeriod = D1 (MetaData "TimePeriod" "Network.AWS.Budgets.Types.Product" "amazonka-budgets-1.5.0-DxVvOYx4s4rzRpD440Wv4" False) (C1 (MetaCons "TimePeriod'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_tpStart") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 POSIX)) (S1 (MetaSel (Just Symbol "_tpEnd") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 POSIX))))

timePeriod Source #

Creates a value of TimePeriod with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

tpStart :: Lens' TimePeriod UTCTime Source #

Undocumented member.

tpEnd :: Lens' TimePeriod UTCTime Source #

Undocumented member.