{-# 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.DeleteAnomalyMonitor
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes a cost anomaly monitor.
module Amazonka.CostExplorer.DeleteAnomalyMonitor
  ( -- * Creating a Request
    DeleteAnomalyMonitor (..),
    newDeleteAnomalyMonitor,

    -- * Request Lenses
    deleteAnomalyMonitor_monitorArn,

    -- * Destructuring the Response
    DeleteAnomalyMonitorResponse (..),
    newDeleteAnomalyMonitorResponse,

    -- * Response Lenses
    deleteAnomalyMonitorResponse_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:/ 'newDeleteAnomalyMonitor' smart constructor.
data DeleteAnomalyMonitor = DeleteAnomalyMonitor'
  { -- | The unique identifier of the cost anomaly monitor that you want to
    -- delete.
    DeleteAnomalyMonitor -> Text
monitorArn :: Prelude.Text
  }
  deriving (DeleteAnomalyMonitor -> DeleteAnomalyMonitor -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteAnomalyMonitor -> DeleteAnomalyMonitor -> Bool
$c/= :: DeleteAnomalyMonitor -> DeleteAnomalyMonitor -> Bool
== :: DeleteAnomalyMonitor -> DeleteAnomalyMonitor -> Bool
$c== :: DeleteAnomalyMonitor -> DeleteAnomalyMonitor -> Bool
Prelude.Eq, ReadPrec [DeleteAnomalyMonitor]
ReadPrec DeleteAnomalyMonitor
Int -> ReadS DeleteAnomalyMonitor
ReadS [DeleteAnomalyMonitor]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteAnomalyMonitor]
$creadListPrec :: ReadPrec [DeleteAnomalyMonitor]
readPrec :: ReadPrec DeleteAnomalyMonitor
$creadPrec :: ReadPrec DeleteAnomalyMonitor
readList :: ReadS [DeleteAnomalyMonitor]
$creadList :: ReadS [DeleteAnomalyMonitor]
readsPrec :: Int -> ReadS DeleteAnomalyMonitor
$creadsPrec :: Int -> ReadS DeleteAnomalyMonitor
Prelude.Read, Int -> DeleteAnomalyMonitor -> ShowS
[DeleteAnomalyMonitor] -> ShowS
DeleteAnomalyMonitor -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteAnomalyMonitor] -> ShowS
$cshowList :: [DeleteAnomalyMonitor] -> ShowS
show :: DeleteAnomalyMonitor -> String
$cshow :: DeleteAnomalyMonitor -> String
showsPrec :: Int -> DeleteAnomalyMonitor -> ShowS
$cshowsPrec :: Int -> DeleteAnomalyMonitor -> ShowS
Prelude.Show, forall x. Rep DeleteAnomalyMonitor x -> DeleteAnomalyMonitor
forall x. DeleteAnomalyMonitor -> Rep DeleteAnomalyMonitor x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteAnomalyMonitor x -> DeleteAnomalyMonitor
$cfrom :: forall x. DeleteAnomalyMonitor -> Rep DeleteAnomalyMonitor x
Prelude.Generic)

-- |
-- Create a value of 'DeleteAnomalyMonitor' 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:
--
-- 'monitorArn', 'deleteAnomalyMonitor_monitorArn' - The unique identifier of the cost anomaly monitor that you want to
-- delete.
newDeleteAnomalyMonitor ::
  -- | 'monitorArn'
  Prelude.Text ->
  DeleteAnomalyMonitor
newDeleteAnomalyMonitor :: Text -> DeleteAnomalyMonitor
newDeleteAnomalyMonitor Text
pMonitorArn_ =
  DeleteAnomalyMonitor' {$sel:monitorArn:DeleteAnomalyMonitor' :: Text
monitorArn = Text
pMonitorArn_}

-- | The unique identifier of the cost anomaly monitor that you want to
-- delete.
deleteAnomalyMonitor_monitorArn :: Lens.Lens' DeleteAnomalyMonitor Prelude.Text
deleteAnomalyMonitor_monitorArn :: Lens' DeleteAnomalyMonitor Text
deleteAnomalyMonitor_monitorArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteAnomalyMonitor' {Text
monitorArn :: Text
$sel:monitorArn:DeleteAnomalyMonitor' :: DeleteAnomalyMonitor -> Text
monitorArn} -> Text
monitorArn) (\s :: DeleteAnomalyMonitor
s@DeleteAnomalyMonitor' {} Text
a -> DeleteAnomalyMonitor
s {$sel:monitorArn:DeleteAnomalyMonitor' :: Text
monitorArn = Text
a} :: DeleteAnomalyMonitor)

instance Core.AWSRequest DeleteAnomalyMonitor where
  type
    AWSResponse DeleteAnomalyMonitor =
      DeleteAnomalyMonitorResponse
  request :: (Service -> Service)
-> DeleteAnomalyMonitor -> Request DeleteAnomalyMonitor
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 DeleteAnomalyMonitor
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteAnomalyMonitor)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> DeleteAnomalyMonitorResponse
DeleteAnomalyMonitorResponse'
            forall (f :: * -> *) a b. Functor 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 DeleteAnomalyMonitor where
  hashWithSalt :: Int -> DeleteAnomalyMonitor -> Int
hashWithSalt Int
_salt DeleteAnomalyMonitor' {Text
monitorArn :: Text
$sel:monitorArn:DeleteAnomalyMonitor' :: DeleteAnomalyMonitor -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
monitorArn

instance Prelude.NFData DeleteAnomalyMonitor where
  rnf :: DeleteAnomalyMonitor -> ()
rnf DeleteAnomalyMonitor' {Text
monitorArn :: Text
$sel:monitorArn:DeleteAnomalyMonitor' :: DeleteAnomalyMonitor -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
monitorArn

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

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

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

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

-- |
-- Create a value of 'DeleteAnomalyMonitorResponse' 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:
--
-- 'httpStatus', 'deleteAnomalyMonitorResponse_httpStatus' - The response's http status code.
newDeleteAnomalyMonitorResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteAnomalyMonitorResponse
newDeleteAnomalyMonitorResponse :: Int -> DeleteAnomalyMonitorResponse
newDeleteAnomalyMonitorResponse Int
pHttpStatus_ =
  DeleteAnomalyMonitorResponse'
    { $sel:httpStatus:DeleteAnomalyMonitorResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

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

instance Prelude.NFData DeleteAnomalyMonitorResponse where
  rnf :: DeleteAnomalyMonitorResponse -> ()
rnf DeleteAnomalyMonitorResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteAnomalyMonitorResponse' :: DeleteAnomalyMonitorResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus