{-# 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.CostAllocationTag
-- 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.CostAllocationTag where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import Amazonka.CostExplorer.Types.CostAllocationTagStatus
import Amazonka.CostExplorer.Types.CostAllocationTagType
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

-- | The cost allocation tag structure. This includes detailed metadata for
-- the @CostAllocationTag@ object.
--
-- /See:/ 'newCostAllocationTag' smart constructor.
data CostAllocationTag = CostAllocationTag'
  { -- | The key for the cost allocation tag.
    CostAllocationTag -> Text
tagKey :: Prelude.Text,
    -- | The type of cost allocation tag. You can use @AWSGenerated@ or
    -- @UserDefined@ type tags. @AWSGenerated@ type tags are tags that Amazon
    -- Web Services defines and applies to support Amazon Web Services
    -- resources for cost allocation purposes. @UserDefined@ type tags are tags
    -- that you define, create, and apply to resources.
    CostAllocationTag -> CostAllocationTagType
type' :: CostAllocationTagType,
    -- | The status of a cost allocation tag.
    CostAllocationTag -> CostAllocationTagStatus
status :: CostAllocationTagStatus
  }
  deriving (CostAllocationTag -> CostAllocationTag -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CostAllocationTag -> CostAllocationTag -> Bool
$c/= :: CostAllocationTag -> CostAllocationTag -> Bool
== :: CostAllocationTag -> CostAllocationTag -> Bool
$c== :: CostAllocationTag -> CostAllocationTag -> Bool
Prelude.Eq, ReadPrec [CostAllocationTag]
ReadPrec CostAllocationTag
Int -> ReadS CostAllocationTag
ReadS [CostAllocationTag]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CostAllocationTag]
$creadListPrec :: ReadPrec [CostAllocationTag]
readPrec :: ReadPrec CostAllocationTag
$creadPrec :: ReadPrec CostAllocationTag
readList :: ReadS [CostAllocationTag]
$creadList :: ReadS [CostAllocationTag]
readsPrec :: Int -> ReadS CostAllocationTag
$creadsPrec :: Int -> ReadS CostAllocationTag
Prelude.Read, Int -> CostAllocationTag -> ShowS
[CostAllocationTag] -> ShowS
CostAllocationTag -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CostAllocationTag] -> ShowS
$cshowList :: [CostAllocationTag] -> ShowS
show :: CostAllocationTag -> String
$cshow :: CostAllocationTag -> String
showsPrec :: Int -> CostAllocationTag -> ShowS
$cshowsPrec :: Int -> CostAllocationTag -> ShowS
Prelude.Show, forall x. Rep CostAllocationTag x -> CostAllocationTag
forall x. CostAllocationTag -> Rep CostAllocationTag x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CostAllocationTag x -> CostAllocationTag
$cfrom :: forall x. CostAllocationTag -> Rep CostAllocationTag x
Prelude.Generic)

-- |
-- Create a value of 'CostAllocationTag' 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:
--
-- 'tagKey', 'costAllocationTag_tagKey' - The key for the cost allocation tag.
--
-- 'type'', 'costAllocationTag_type' - The type of cost allocation tag. You can use @AWSGenerated@ or
-- @UserDefined@ type tags. @AWSGenerated@ type tags are tags that Amazon
-- Web Services defines and applies to support Amazon Web Services
-- resources for cost allocation purposes. @UserDefined@ type tags are tags
-- that you define, create, and apply to resources.
--
-- 'status', 'costAllocationTag_status' - The status of a cost allocation tag.
newCostAllocationTag ::
  -- | 'tagKey'
  Prelude.Text ->
  -- | 'type''
  CostAllocationTagType ->
  -- | 'status'
  CostAllocationTagStatus ->
  CostAllocationTag
newCostAllocationTag :: Text
-> CostAllocationTagType
-> CostAllocationTagStatus
-> CostAllocationTag
newCostAllocationTag Text
pTagKey_ CostAllocationTagType
pType_ CostAllocationTagStatus
pStatus_ =
  CostAllocationTag'
    { $sel:tagKey:CostAllocationTag' :: Text
tagKey = Text
pTagKey_,
      $sel:type':CostAllocationTag' :: CostAllocationTagType
type' = CostAllocationTagType
pType_,
      $sel:status:CostAllocationTag' :: CostAllocationTagStatus
status = CostAllocationTagStatus
pStatus_
    }

-- | The key for the cost allocation tag.
costAllocationTag_tagKey :: Lens.Lens' CostAllocationTag Prelude.Text
costAllocationTag_tagKey :: Lens' CostAllocationTag Text
costAllocationTag_tagKey = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CostAllocationTag' {Text
tagKey :: Text
$sel:tagKey:CostAllocationTag' :: CostAllocationTag -> Text
tagKey} -> Text
tagKey) (\s :: CostAllocationTag
s@CostAllocationTag' {} Text
a -> CostAllocationTag
s {$sel:tagKey:CostAllocationTag' :: Text
tagKey = Text
a} :: CostAllocationTag)

-- | The type of cost allocation tag. You can use @AWSGenerated@ or
-- @UserDefined@ type tags. @AWSGenerated@ type tags are tags that Amazon
-- Web Services defines and applies to support Amazon Web Services
-- resources for cost allocation purposes. @UserDefined@ type tags are tags
-- that you define, create, and apply to resources.
costAllocationTag_type :: Lens.Lens' CostAllocationTag CostAllocationTagType
costAllocationTag_type :: Lens' CostAllocationTag CostAllocationTagType
costAllocationTag_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CostAllocationTag' {CostAllocationTagType
type' :: CostAllocationTagType
$sel:type':CostAllocationTag' :: CostAllocationTag -> CostAllocationTagType
type'} -> CostAllocationTagType
type') (\s :: CostAllocationTag
s@CostAllocationTag' {} CostAllocationTagType
a -> CostAllocationTag
s {$sel:type':CostAllocationTag' :: CostAllocationTagType
type' = CostAllocationTagType
a} :: CostAllocationTag)

-- | The status of a cost allocation tag.
costAllocationTag_status :: Lens.Lens' CostAllocationTag CostAllocationTagStatus
costAllocationTag_status :: Lens' CostAllocationTag CostAllocationTagStatus
costAllocationTag_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CostAllocationTag' {CostAllocationTagStatus
status :: CostAllocationTagStatus
$sel:status:CostAllocationTag' :: CostAllocationTag -> CostAllocationTagStatus
status} -> CostAllocationTagStatus
status) (\s :: CostAllocationTag
s@CostAllocationTag' {} CostAllocationTagStatus
a -> CostAllocationTag
s {$sel:status:CostAllocationTag' :: CostAllocationTagStatus
status = CostAllocationTagStatus
a} :: CostAllocationTag)

instance Data.FromJSON CostAllocationTag where
  parseJSON :: Value -> Parser CostAllocationTag
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"CostAllocationTag"
      ( \Object
x ->
          Text
-> CostAllocationTagType
-> CostAllocationTagStatus
-> CostAllocationTag
CostAllocationTag'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"TagKey")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser 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 a
Data..: Key
"Status")
      )

instance Prelude.Hashable CostAllocationTag where
  hashWithSalt :: Int -> CostAllocationTag -> Int
hashWithSalt Int
_salt CostAllocationTag' {Text
CostAllocationTagStatus
CostAllocationTagType
status :: CostAllocationTagStatus
type' :: CostAllocationTagType
tagKey :: Text
$sel:status:CostAllocationTag' :: CostAllocationTag -> CostAllocationTagStatus
$sel:type':CostAllocationTag' :: CostAllocationTag -> CostAllocationTagType
$sel:tagKey:CostAllocationTag' :: CostAllocationTag -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
tagKey
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` CostAllocationTagType
type'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` CostAllocationTagStatus
status

instance Prelude.NFData CostAllocationTag where
  rnf :: CostAllocationTag -> ()
rnf CostAllocationTag' {Text
CostAllocationTagStatus
CostAllocationTagType
status :: CostAllocationTagStatus
type' :: CostAllocationTagType
tagKey :: Text
$sel:status:CostAllocationTag' :: CostAllocationTag -> CostAllocationTagStatus
$sel:type':CostAllocationTag' :: CostAllocationTag -> CostAllocationTagType
$sel:tagKey:CostAllocationTag' :: CostAllocationTag -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
tagKey
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf CostAllocationTagType
type'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf CostAllocationTagStatus
status