{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# 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.DescribeCostCategoryDefinition
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns the name, Amazon Resource Name (ARN), rules, definition, and
-- effective dates of a Cost Category that\'s defined in the account.
--
-- You have the option to use @EffectiveOn@ to return a Cost Category
-- that\'s active on a specific date. If there\'s no @EffectiveOn@
-- specified, you see a Cost Category that\'s effective on the current
-- date. If Cost Category is still effective, @EffectiveEnd@ is omitted in
-- the response.
module Amazonka.CostExplorer.DescribeCostCategoryDefinition
  ( -- * Creating a Request
    DescribeCostCategoryDefinition (..),
    newDescribeCostCategoryDefinition,

    -- * Request Lenses
    describeCostCategoryDefinition_effectiveOn,
    describeCostCategoryDefinition_costCategoryArn,

    -- * Destructuring the Response
    DescribeCostCategoryDefinitionResponse (..),
    newDescribeCostCategoryDefinitionResponse,

    -- * Response Lenses
    describeCostCategoryDefinitionResponse_costCategory,
    describeCostCategoryDefinitionResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import Amazonka.CostExplorer.Types
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDescribeCostCategoryDefinition' smart constructor.
data DescribeCostCategoryDefinition = DescribeCostCategoryDefinition'
  { -- | The date when the Cost Category was effective.
    DescribeCostCategoryDefinition -> Maybe Text
effectiveOn :: Prelude.Maybe Prelude.Text,
    -- | The unique identifier for your Cost Category.
    DescribeCostCategoryDefinition -> Text
costCategoryArn :: Prelude.Text
  }
  deriving (DescribeCostCategoryDefinition
-> DescribeCostCategoryDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeCostCategoryDefinition
-> DescribeCostCategoryDefinition -> Bool
$c/= :: DescribeCostCategoryDefinition
-> DescribeCostCategoryDefinition -> Bool
== :: DescribeCostCategoryDefinition
-> DescribeCostCategoryDefinition -> Bool
$c== :: DescribeCostCategoryDefinition
-> DescribeCostCategoryDefinition -> Bool
Prelude.Eq, ReadPrec [DescribeCostCategoryDefinition]
ReadPrec DescribeCostCategoryDefinition
Int -> ReadS DescribeCostCategoryDefinition
ReadS [DescribeCostCategoryDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeCostCategoryDefinition]
$creadListPrec :: ReadPrec [DescribeCostCategoryDefinition]
readPrec :: ReadPrec DescribeCostCategoryDefinition
$creadPrec :: ReadPrec DescribeCostCategoryDefinition
readList :: ReadS [DescribeCostCategoryDefinition]
$creadList :: ReadS [DescribeCostCategoryDefinition]
readsPrec :: Int -> ReadS DescribeCostCategoryDefinition
$creadsPrec :: Int -> ReadS DescribeCostCategoryDefinition
Prelude.Read, Int -> DescribeCostCategoryDefinition -> ShowS
[DescribeCostCategoryDefinition] -> ShowS
DescribeCostCategoryDefinition -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeCostCategoryDefinition] -> ShowS
$cshowList :: [DescribeCostCategoryDefinition] -> ShowS
show :: DescribeCostCategoryDefinition -> String
$cshow :: DescribeCostCategoryDefinition -> String
showsPrec :: Int -> DescribeCostCategoryDefinition -> ShowS
$cshowsPrec :: Int -> DescribeCostCategoryDefinition -> ShowS
Prelude.Show, forall x.
Rep DescribeCostCategoryDefinition x
-> DescribeCostCategoryDefinition
forall x.
DescribeCostCategoryDefinition
-> Rep DescribeCostCategoryDefinition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeCostCategoryDefinition x
-> DescribeCostCategoryDefinition
$cfrom :: forall x.
DescribeCostCategoryDefinition
-> Rep DescribeCostCategoryDefinition x
Prelude.Generic)

-- |
-- Create a value of 'DescribeCostCategoryDefinition' 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:
--
-- 'effectiveOn', 'describeCostCategoryDefinition_effectiveOn' - The date when the Cost Category was effective.
--
-- 'costCategoryArn', 'describeCostCategoryDefinition_costCategoryArn' - The unique identifier for your Cost Category.
newDescribeCostCategoryDefinition ::
  -- | 'costCategoryArn'
  Prelude.Text ->
  DescribeCostCategoryDefinition
newDescribeCostCategoryDefinition :: Text -> DescribeCostCategoryDefinition
newDescribeCostCategoryDefinition Text
pCostCategoryArn_ =
  DescribeCostCategoryDefinition'
    { $sel:effectiveOn:DescribeCostCategoryDefinition' :: Maybe Text
effectiveOn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:costCategoryArn:DescribeCostCategoryDefinition' :: Text
costCategoryArn = Text
pCostCategoryArn_
    }

-- | The date when the Cost Category was effective.
describeCostCategoryDefinition_effectiveOn :: Lens.Lens' DescribeCostCategoryDefinition (Prelude.Maybe Prelude.Text)
describeCostCategoryDefinition_effectiveOn :: Lens' DescribeCostCategoryDefinition (Maybe Text)
describeCostCategoryDefinition_effectiveOn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCostCategoryDefinition' {Maybe Text
effectiveOn :: Maybe Text
$sel:effectiveOn:DescribeCostCategoryDefinition' :: DescribeCostCategoryDefinition -> Maybe Text
effectiveOn} -> Maybe Text
effectiveOn) (\s :: DescribeCostCategoryDefinition
s@DescribeCostCategoryDefinition' {} Maybe Text
a -> DescribeCostCategoryDefinition
s {$sel:effectiveOn:DescribeCostCategoryDefinition' :: Maybe Text
effectiveOn = Maybe Text
a} :: DescribeCostCategoryDefinition)

-- | The unique identifier for your Cost Category.
describeCostCategoryDefinition_costCategoryArn :: Lens.Lens' DescribeCostCategoryDefinition Prelude.Text
describeCostCategoryDefinition_costCategoryArn :: Lens' DescribeCostCategoryDefinition Text
describeCostCategoryDefinition_costCategoryArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCostCategoryDefinition' {Text
costCategoryArn :: Text
$sel:costCategoryArn:DescribeCostCategoryDefinition' :: DescribeCostCategoryDefinition -> Text
costCategoryArn} -> Text
costCategoryArn) (\s :: DescribeCostCategoryDefinition
s@DescribeCostCategoryDefinition' {} Text
a -> DescribeCostCategoryDefinition
s {$sel:costCategoryArn:DescribeCostCategoryDefinition' :: Text
costCategoryArn = Text
a} :: DescribeCostCategoryDefinition)

instance
  Core.AWSRequest
    DescribeCostCategoryDefinition
  where
  type
    AWSResponse DescribeCostCategoryDefinition =
      DescribeCostCategoryDefinitionResponse
  request :: (Service -> Service)
-> DescribeCostCategoryDefinition
-> Request DescribeCostCategoryDefinition
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeCostCategoryDefinition
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse DescribeCostCategoryDefinition)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe CostCategory -> Int -> DescribeCostCategoryDefinitionResponse
DescribeCostCategoryDefinitionResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"CostCategory")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance
  Prelude.Hashable
    DescribeCostCategoryDefinition
  where
  hashWithSalt :: Int -> DescribeCostCategoryDefinition -> Int
hashWithSalt
    Int
_salt
    DescribeCostCategoryDefinition' {Maybe Text
Text
costCategoryArn :: Text
effectiveOn :: Maybe Text
$sel:costCategoryArn:DescribeCostCategoryDefinition' :: DescribeCostCategoryDefinition -> Text
$sel:effectiveOn:DescribeCostCategoryDefinition' :: DescribeCostCategoryDefinition -> Maybe Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
effectiveOn
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
costCategoryArn

instance
  Prelude.NFData
    DescribeCostCategoryDefinition
  where
  rnf :: DescribeCostCategoryDefinition -> ()
rnf DescribeCostCategoryDefinition' {Maybe Text
Text
costCategoryArn :: Text
effectiveOn :: Maybe Text
$sel:costCategoryArn:DescribeCostCategoryDefinition' :: DescribeCostCategoryDefinition -> Text
$sel:effectiveOn:DescribeCostCategoryDefinition' :: DescribeCostCategoryDefinition -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
effectiveOn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
costCategoryArn

instance
  Data.ToHeaders
    DescribeCostCategoryDefinition
  where
  toHeaders :: DescribeCostCategoryDefinition -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AWSInsightsIndexService.DescribeCostCategoryDefinition" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DescribeCostCategoryDefinition where
  toJSON :: DescribeCostCategoryDefinition -> Value
toJSON DescribeCostCategoryDefinition' {Maybe Text
Text
costCategoryArn :: Text
effectiveOn :: Maybe Text
$sel:costCategoryArn:DescribeCostCategoryDefinition' :: DescribeCostCategoryDefinition -> Text
$sel:effectiveOn:DescribeCostCategoryDefinition' :: DescribeCostCategoryDefinition -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"EffectiveOn" 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
effectiveOn,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"CostCategoryArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
costCategoryArn)
          ]
      )

instance Data.ToPath DescribeCostCategoryDefinition where
  toPath :: DescribeCostCategoryDefinition -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery DescribeCostCategoryDefinition where
  toQuery :: DescribeCostCategoryDefinition -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newDescribeCostCategoryDefinitionResponse' smart constructor.
data DescribeCostCategoryDefinitionResponse = DescribeCostCategoryDefinitionResponse'
  { DescribeCostCategoryDefinitionResponse -> Maybe CostCategory
costCategory :: Prelude.Maybe CostCategory,
    -- | The response's http status code.
    DescribeCostCategoryDefinitionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeCostCategoryDefinitionResponse
-> DescribeCostCategoryDefinitionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeCostCategoryDefinitionResponse
-> DescribeCostCategoryDefinitionResponse -> Bool
$c/= :: DescribeCostCategoryDefinitionResponse
-> DescribeCostCategoryDefinitionResponse -> Bool
== :: DescribeCostCategoryDefinitionResponse
-> DescribeCostCategoryDefinitionResponse -> Bool
$c== :: DescribeCostCategoryDefinitionResponse
-> DescribeCostCategoryDefinitionResponse -> Bool
Prelude.Eq, ReadPrec [DescribeCostCategoryDefinitionResponse]
ReadPrec DescribeCostCategoryDefinitionResponse
Int -> ReadS DescribeCostCategoryDefinitionResponse
ReadS [DescribeCostCategoryDefinitionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeCostCategoryDefinitionResponse]
$creadListPrec :: ReadPrec [DescribeCostCategoryDefinitionResponse]
readPrec :: ReadPrec DescribeCostCategoryDefinitionResponse
$creadPrec :: ReadPrec DescribeCostCategoryDefinitionResponse
readList :: ReadS [DescribeCostCategoryDefinitionResponse]
$creadList :: ReadS [DescribeCostCategoryDefinitionResponse]
readsPrec :: Int -> ReadS DescribeCostCategoryDefinitionResponse
$creadsPrec :: Int -> ReadS DescribeCostCategoryDefinitionResponse
Prelude.Read, Int -> DescribeCostCategoryDefinitionResponse -> ShowS
[DescribeCostCategoryDefinitionResponse] -> ShowS
DescribeCostCategoryDefinitionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeCostCategoryDefinitionResponse] -> ShowS
$cshowList :: [DescribeCostCategoryDefinitionResponse] -> ShowS
show :: DescribeCostCategoryDefinitionResponse -> String
$cshow :: DescribeCostCategoryDefinitionResponse -> String
showsPrec :: Int -> DescribeCostCategoryDefinitionResponse -> ShowS
$cshowsPrec :: Int -> DescribeCostCategoryDefinitionResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeCostCategoryDefinitionResponse x
-> DescribeCostCategoryDefinitionResponse
forall x.
DescribeCostCategoryDefinitionResponse
-> Rep DescribeCostCategoryDefinitionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeCostCategoryDefinitionResponse x
-> DescribeCostCategoryDefinitionResponse
$cfrom :: forall x.
DescribeCostCategoryDefinitionResponse
-> Rep DescribeCostCategoryDefinitionResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeCostCategoryDefinitionResponse' 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:
--
-- 'costCategory', 'describeCostCategoryDefinitionResponse_costCategory' - Undocumented member.
--
-- 'httpStatus', 'describeCostCategoryDefinitionResponse_httpStatus' - The response's http status code.
newDescribeCostCategoryDefinitionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeCostCategoryDefinitionResponse
newDescribeCostCategoryDefinitionResponse :: Int -> DescribeCostCategoryDefinitionResponse
newDescribeCostCategoryDefinitionResponse
  Int
pHttpStatus_ =
    DescribeCostCategoryDefinitionResponse'
      { $sel:costCategory:DescribeCostCategoryDefinitionResponse' :: Maybe CostCategory
costCategory =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeCostCategoryDefinitionResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | Undocumented member.
describeCostCategoryDefinitionResponse_costCategory :: Lens.Lens' DescribeCostCategoryDefinitionResponse (Prelude.Maybe CostCategory)
describeCostCategoryDefinitionResponse_costCategory :: Lens' DescribeCostCategoryDefinitionResponse (Maybe CostCategory)
describeCostCategoryDefinitionResponse_costCategory = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCostCategoryDefinitionResponse' {Maybe CostCategory
costCategory :: Maybe CostCategory
$sel:costCategory:DescribeCostCategoryDefinitionResponse' :: DescribeCostCategoryDefinitionResponse -> Maybe CostCategory
costCategory} -> Maybe CostCategory
costCategory) (\s :: DescribeCostCategoryDefinitionResponse
s@DescribeCostCategoryDefinitionResponse' {} Maybe CostCategory
a -> DescribeCostCategoryDefinitionResponse
s {$sel:costCategory:DescribeCostCategoryDefinitionResponse' :: Maybe CostCategory
costCategory = Maybe CostCategory
a} :: DescribeCostCategoryDefinitionResponse)

-- | The response's http status code.
describeCostCategoryDefinitionResponse_httpStatus :: Lens.Lens' DescribeCostCategoryDefinitionResponse Prelude.Int
describeCostCategoryDefinitionResponse_httpStatus :: Lens' DescribeCostCategoryDefinitionResponse Int
describeCostCategoryDefinitionResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCostCategoryDefinitionResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeCostCategoryDefinitionResponse' :: DescribeCostCategoryDefinitionResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeCostCategoryDefinitionResponse
s@DescribeCostCategoryDefinitionResponse' {} Int
a -> DescribeCostCategoryDefinitionResponse
s {$sel:httpStatus:DescribeCostCategoryDefinitionResponse' :: Int
httpStatus = Int
a} :: DescribeCostCategoryDefinitionResponse)

instance
  Prelude.NFData
    DescribeCostCategoryDefinitionResponse
  where
  rnf :: DescribeCostCategoryDefinitionResponse -> ()
rnf DescribeCostCategoryDefinitionResponse' {Int
Maybe CostCategory
httpStatus :: Int
costCategory :: Maybe CostCategory
$sel:httpStatus:DescribeCostCategoryDefinitionResponse' :: DescribeCostCategoryDefinitionResponse -> Int
$sel:costCategory:DescribeCostCategoryDefinitionResponse' :: DescribeCostCategoryDefinitionResponse -> Maybe CostCategory
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe CostCategory
costCategory
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus