{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.CostExplorer.Types.CostCategoryRule
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.CostExplorer.Types.CostCategoryRule where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import Amazonka.CostExplorer.Types.CostCategoryInheritedValueDimension
import Amazonka.CostExplorer.Types.CostCategoryRuleType
import Amazonka.CostExplorer.Types.Expression
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

-- | Rules are processed in order. If there are multiple rules that match the
-- line item, then the first rule to match is used to determine that Cost
-- Category value.
--
-- /See:/ 'newCostCategoryRule' smart constructor.
data CostCategoryRule = CostCategoryRule'
  { -- | The value the line item is categorized as if the line item contains the
    -- matched dimension.
    CostCategoryRule -> Maybe CostCategoryInheritedValueDimension
inheritedValue :: Prelude.Maybe CostCategoryInheritedValueDimension,
    -- | An
    -- <https://docs.aws.amazon.com/aws-cost-management/latest/APIReference/API_Expression.html Expression>
    -- object used to categorize costs. This supports dimensions, tags, and
    -- nested expressions. Currently the only dimensions supported are
    -- @LINKED_ACCOUNT@, @SERVICE_CODE@, @RECORD_TYPE@, and
    -- @LINKED_ACCOUNT_NAME@.
    --
    -- Root level @OR@ isn\'t supported. We recommend that you create a
    -- separate rule instead.
    --
    -- @RECORD_TYPE@ is a dimension used for Cost Explorer APIs, and is also
    -- supported for Cost Category expressions. This dimension uses different
    -- terms, depending on whether you\'re using the console or API\/JSON
    -- editor. For a detailed comparison, see
    -- <https://docs.aws.amazon.com/awsaccountbilling/latest/aboutv2/manage-cost-categories.html#cost-categories-terms Term Comparisons>
    -- in the /Billing and Cost Management User Guide/.
    CostCategoryRule -> Maybe Expression
rule :: Prelude.Maybe Expression,
    -- | You can define the @CostCategoryRule@ rule type as either @REGULAR@ or
    -- @INHERITED_VALUE@. The @INHERITED_VALUE@ rule type adds the flexibility
    -- to define a rule that dynamically inherits the cost category value. This
    -- value is from the dimension value that\'s defined by
    -- @CostCategoryInheritedValueDimension@. For example, suppose that you
    -- want to costs to be dynamically grouped based on the value of a specific
    -- tag key. First, choose an inherited value rule type, and then choose the
    -- tag dimension and specify the tag key to use.
    CostCategoryRule -> Maybe CostCategoryRuleType
type' :: Prelude.Maybe CostCategoryRuleType,
    CostCategoryRule -> Maybe Text
value :: Prelude.Maybe Prelude.Text
  }
  deriving (CostCategoryRule -> CostCategoryRule -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CostCategoryRule -> CostCategoryRule -> Bool
$c/= :: CostCategoryRule -> CostCategoryRule -> Bool
== :: CostCategoryRule -> CostCategoryRule -> Bool
$c== :: CostCategoryRule -> CostCategoryRule -> Bool
Prelude.Eq, ReadPrec [CostCategoryRule]
ReadPrec CostCategoryRule
Int -> ReadS CostCategoryRule
ReadS [CostCategoryRule]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CostCategoryRule]
$creadListPrec :: ReadPrec [CostCategoryRule]
readPrec :: ReadPrec CostCategoryRule
$creadPrec :: ReadPrec CostCategoryRule
readList :: ReadS [CostCategoryRule]
$creadList :: ReadS [CostCategoryRule]
readsPrec :: Int -> ReadS CostCategoryRule
$creadsPrec :: Int -> ReadS CostCategoryRule
Prelude.Read, Int -> CostCategoryRule -> ShowS
[CostCategoryRule] -> ShowS
CostCategoryRule -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CostCategoryRule] -> ShowS
$cshowList :: [CostCategoryRule] -> ShowS
show :: CostCategoryRule -> String
$cshow :: CostCategoryRule -> String
showsPrec :: Int -> CostCategoryRule -> ShowS
$cshowsPrec :: Int -> CostCategoryRule -> ShowS
Prelude.Show, forall x. Rep CostCategoryRule x -> CostCategoryRule
forall x. CostCategoryRule -> Rep CostCategoryRule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CostCategoryRule x -> CostCategoryRule
$cfrom :: forall x. CostCategoryRule -> Rep CostCategoryRule x
Prelude.Generic)

-- |
-- Create a value of 'CostCategoryRule' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'inheritedValue', 'costCategoryRule_inheritedValue' - The value the line item is categorized as if the line item contains the
-- matched dimension.
--
-- 'rule', 'costCategoryRule_rule' - An
-- <https://docs.aws.amazon.com/aws-cost-management/latest/APIReference/API_Expression.html Expression>
-- object used to categorize costs. This supports dimensions, tags, and
-- nested expressions. Currently the only dimensions supported are
-- @LINKED_ACCOUNT@, @SERVICE_CODE@, @RECORD_TYPE@, and
-- @LINKED_ACCOUNT_NAME@.
--
-- Root level @OR@ isn\'t supported. We recommend that you create a
-- separate rule instead.
--
-- @RECORD_TYPE@ is a dimension used for Cost Explorer APIs, and is also
-- supported for Cost Category expressions. This dimension uses different
-- terms, depending on whether you\'re using the console or API\/JSON
-- editor. For a detailed comparison, see
-- <https://docs.aws.amazon.com/awsaccountbilling/latest/aboutv2/manage-cost-categories.html#cost-categories-terms Term Comparisons>
-- in the /Billing and Cost Management User Guide/.
--
-- 'type'', 'costCategoryRule_type' - You can define the @CostCategoryRule@ rule type as either @REGULAR@ or
-- @INHERITED_VALUE@. The @INHERITED_VALUE@ rule type adds the flexibility
-- to define a rule that dynamically inherits the cost category value. This
-- value is from the dimension value that\'s defined by
-- @CostCategoryInheritedValueDimension@. For example, suppose that you
-- want to costs to be dynamically grouped based on the value of a specific
-- tag key. First, choose an inherited value rule type, and then choose the
-- tag dimension and specify the tag key to use.
--
-- 'value', 'costCategoryRule_value' - Undocumented member.
newCostCategoryRule ::
  CostCategoryRule
newCostCategoryRule :: CostCategoryRule
newCostCategoryRule =
  CostCategoryRule'
    { $sel:inheritedValue:CostCategoryRule' :: Maybe CostCategoryInheritedValueDimension
inheritedValue = forall a. Maybe a
Prelude.Nothing,
      $sel:rule:CostCategoryRule' :: Maybe Expression
rule = forall a. Maybe a
Prelude.Nothing,
      $sel:type':CostCategoryRule' :: Maybe CostCategoryRuleType
type' = forall a. Maybe a
Prelude.Nothing,
      $sel:value:CostCategoryRule' :: Maybe Text
value = forall a. Maybe a
Prelude.Nothing
    }

-- | The value the line item is categorized as if the line item contains the
-- matched dimension.
costCategoryRule_inheritedValue :: Lens.Lens' CostCategoryRule (Prelude.Maybe CostCategoryInheritedValueDimension)
costCategoryRule_inheritedValue :: Lens' CostCategoryRule (Maybe CostCategoryInheritedValueDimension)
costCategoryRule_inheritedValue = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CostCategoryRule' {Maybe CostCategoryInheritedValueDimension
inheritedValue :: Maybe CostCategoryInheritedValueDimension
$sel:inheritedValue:CostCategoryRule' :: CostCategoryRule -> Maybe CostCategoryInheritedValueDimension
inheritedValue} -> Maybe CostCategoryInheritedValueDimension
inheritedValue) (\s :: CostCategoryRule
s@CostCategoryRule' {} Maybe CostCategoryInheritedValueDimension
a -> CostCategoryRule
s {$sel:inheritedValue:CostCategoryRule' :: Maybe CostCategoryInheritedValueDimension
inheritedValue = Maybe CostCategoryInheritedValueDimension
a} :: CostCategoryRule)

-- | An
-- <https://docs.aws.amazon.com/aws-cost-management/latest/APIReference/API_Expression.html Expression>
-- object used to categorize costs. This supports dimensions, tags, and
-- nested expressions. Currently the only dimensions supported are
-- @LINKED_ACCOUNT@, @SERVICE_CODE@, @RECORD_TYPE@, and
-- @LINKED_ACCOUNT_NAME@.
--
-- Root level @OR@ isn\'t supported. We recommend that you create a
-- separate rule instead.
--
-- @RECORD_TYPE@ is a dimension used for Cost Explorer APIs, and is also
-- supported for Cost Category expressions. This dimension uses different
-- terms, depending on whether you\'re using the console or API\/JSON
-- editor. For a detailed comparison, see
-- <https://docs.aws.amazon.com/awsaccountbilling/latest/aboutv2/manage-cost-categories.html#cost-categories-terms Term Comparisons>
-- in the /Billing and Cost Management User Guide/.
costCategoryRule_rule :: Lens.Lens' CostCategoryRule (Prelude.Maybe Expression)
costCategoryRule_rule :: Lens' CostCategoryRule (Maybe Expression)
costCategoryRule_rule = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CostCategoryRule' {Maybe Expression
rule :: Maybe Expression
$sel:rule:CostCategoryRule' :: CostCategoryRule -> Maybe Expression
rule} -> Maybe Expression
rule) (\s :: CostCategoryRule
s@CostCategoryRule' {} Maybe Expression
a -> CostCategoryRule
s {$sel:rule:CostCategoryRule' :: Maybe Expression
rule = Maybe Expression
a} :: CostCategoryRule)

-- | You can define the @CostCategoryRule@ rule type as either @REGULAR@ or
-- @INHERITED_VALUE@. The @INHERITED_VALUE@ rule type adds the flexibility
-- to define a rule that dynamically inherits the cost category value. This
-- value is from the dimension value that\'s defined by
-- @CostCategoryInheritedValueDimension@. For example, suppose that you
-- want to costs to be dynamically grouped based on the value of a specific
-- tag key. First, choose an inherited value rule type, and then choose the
-- tag dimension and specify the tag key to use.
costCategoryRule_type :: Lens.Lens' CostCategoryRule (Prelude.Maybe CostCategoryRuleType)
costCategoryRule_type :: Lens' CostCategoryRule (Maybe CostCategoryRuleType)
costCategoryRule_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CostCategoryRule' {Maybe CostCategoryRuleType
type' :: Maybe CostCategoryRuleType
$sel:type':CostCategoryRule' :: CostCategoryRule -> Maybe CostCategoryRuleType
type'} -> Maybe CostCategoryRuleType
type') (\s :: CostCategoryRule
s@CostCategoryRule' {} Maybe CostCategoryRuleType
a -> CostCategoryRule
s {$sel:type':CostCategoryRule' :: Maybe CostCategoryRuleType
type' = Maybe CostCategoryRuleType
a} :: CostCategoryRule)

-- | Undocumented member.
costCategoryRule_value :: Lens.Lens' CostCategoryRule (Prelude.Maybe Prelude.Text)
costCategoryRule_value :: Lens' CostCategoryRule (Maybe Text)
costCategoryRule_value = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CostCategoryRule' {Maybe Text
value :: Maybe Text
$sel:value:CostCategoryRule' :: CostCategoryRule -> Maybe Text
value} -> Maybe Text
value) (\s :: CostCategoryRule
s@CostCategoryRule' {} Maybe Text
a -> CostCategoryRule
s {$sel:value:CostCategoryRule' :: Maybe Text
value = Maybe Text
a} :: CostCategoryRule)

instance Data.FromJSON CostCategoryRule where
  parseJSON :: Value -> Parser CostCategoryRule
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"CostCategoryRule"
      ( \Object
x ->
          Maybe CostCategoryInheritedValueDimension
-> Maybe Expression
-> Maybe CostCategoryRuleType
-> Maybe Text
-> CostCategoryRule
CostCategoryRule'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"InheritedValue")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Rule")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Type")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Value")
      )

instance Prelude.Hashable CostCategoryRule where
  hashWithSalt :: Int -> CostCategoryRule -> Int
hashWithSalt Int
_salt CostCategoryRule' {Maybe Text
Maybe CostCategoryInheritedValueDimension
Maybe CostCategoryRuleType
Maybe Expression
value :: Maybe Text
type' :: Maybe CostCategoryRuleType
rule :: Maybe Expression
inheritedValue :: Maybe CostCategoryInheritedValueDimension
$sel:value:CostCategoryRule' :: CostCategoryRule -> Maybe Text
$sel:type':CostCategoryRule' :: CostCategoryRule -> Maybe CostCategoryRuleType
$sel:rule:CostCategoryRule' :: CostCategoryRule -> Maybe Expression
$sel:inheritedValue:CostCategoryRule' :: CostCategoryRule -> Maybe CostCategoryInheritedValueDimension
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CostCategoryInheritedValueDimension
inheritedValue
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Expression
rule
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CostCategoryRuleType
type'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
value

instance Prelude.NFData CostCategoryRule where
  rnf :: CostCategoryRule -> ()
rnf CostCategoryRule' {Maybe Text
Maybe CostCategoryInheritedValueDimension
Maybe CostCategoryRuleType
Maybe Expression
value :: Maybe Text
type' :: Maybe CostCategoryRuleType
rule :: Maybe Expression
inheritedValue :: Maybe CostCategoryInheritedValueDimension
$sel:value:CostCategoryRule' :: CostCategoryRule -> Maybe Text
$sel:type':CostCategoryRule' :: CostCategoryRule -> Maybe CostCategoryRuleType
$sel:rule:CostCategoryRule' :: CostCategoryRule -> Maybe Expression
$sel:inheritedValue:CostCategoryRule' :: CostCategoryRule -> Maybe CostCategoryInheritedValueDimension
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe CostCategoryInheritedValueDimension
inheritedValue
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Expression
rule
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CostCategoryRuleType
type'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
value

instance Data.ToJSON CostCategoryRule where
  toJSON :: CostCategoryRule -> Value
toJSON CostCategoryRule' {Maybe Text
Maybe CostCategoryInheritedValueDimension
Maybe CostCategoryRuleType
Maybe Expression
value :: Maybe Text
type' :: Maybe CostCategoryRuleType
rule :: Maybe Expression
inheritedValue :: Maybe CostCategoryInheritedValueDimension
$sel:value:CostCategoryRule' :: CostCategoryRule -> Maybe Text
$sel:type':CostCategoryRule' :: CostCategoryRule -> Maybe CostCategoryRuleType
$sel:rule:CostCategoryRule' :: CostCategoryRule -> Maybe Expression
$sel:inheritedValue:CostCategoryRule' :: CostCategoryRule -> Maybe CostCategoryInheritedValueDimension
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"InheritedValue" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CostCategoryInheritedValueDimension
inheritedValue,
            (Key
"Rule" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Expression
rule,
            (Key
"Type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CostCategoryRuleType
type',
            (Key
"Value" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
value
          ]
      )