{-# 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.Lightsail.DeleteAlarm
-- 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 an alarm.
--
-- An alarm is used to monitor a single metric for one of your resources.
-- When a metric condition is met, the alarm can notify you by email, SMS
-- text message, and a banner displayed on the Amazon Lightsail console.
-- For more information, see
-- <https://lightsail.aws.amazon.com/ls/docs/en_us/articles/amazon-lightsail-alarms Alarms in Amazon Lightsail>.
module Amazonka.Lightsail.DeleteAlarm
  ( -- * Creating a Request
    DeleteAlarm (..),
    newDeleteAlarm,

    -- * Request Lenses
    deleteAlarm_alarmName,

    -- * Destructuring the Response
    DeleteAlarmResponse (..),
    newDeleteAlarmResponse,

    -- * Response Lenses
    deleteAlarmResponse_operations,
    deleteAlarmResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDeleteAlarm' smart constructor.
data DeleteAlarm = DeleteAlarm'
  { -- | The name of the alarm to delete.
    DeleteAlarm -> Text
alarmName :: Prelude.Text
  }
  deriving (DeleteAlarm -> DeleteAlarm -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteAlarm -> DeleteAlarm -> Bool
$c/= :: DeleteAlarm -> DeleteAlarm -> Bool
== :: DeleteAlarm -> DeleteAlarm -> Bool
$c== :: DeleteAlarm -> DeleteAlarm -> Bool
Prelude.Eq, ReadPrec [DeleteAlarm]
ReadPrec DeleteAlarm
Int -> ReadS DeleteAlarm
ReadS [DeleteAlarm]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteAlarm]
$creadListPrec :: ReadPrec [DeleteAlarm]
readPrec :: ReadPrec DeleteAlarm
$creadPrec :: ReadPrec DeleteAlarm
readList :: ReadS [DeleteAlarm]
$creadList :: ReadS [DeleteAlarm]
readsPrec :: Int -> ReadS DeleteAlarm
$creadsPrec :: Int -> ReadS DeleteAlarm
Prelude.Read, Int -> DeleteAlarm -> ShowS
[DeleteAlarm] -> ShowS
DeleteAlarm -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteAlarm] -> ShowS
$cshowList :: [DeleteAlarm] -> ShowS
show :: DeleteAlarm -> String
$cshow :: DeleteAlarm -> String
showsPrec :: Int -> DeleteAlarm -> ShowS
$cshowsPrec :: Int -> DeleteAlarm -> ShowS
Prelude.Show, forall x. Rep DeleteAlarm x -> DeleteAlarm
forall x. DeleteAlarm -> Rep DeleteAlarm x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteAlarm x -> DeleteAlarm
$cfrom :: forall x. DeleteAlarm -> Rep DeleteAlarm x
Prelude.Generic)

-- |
-- Create a value of 'DeleteAlarm' 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:
--
-- 'alarmName', 'deleteAlarm_alarmName' - The name of the alarm to delete.
newDeleteAlarm ::
  -- | 'alarmName'
  Prelude.Text ->
  DeleteAlarm
newDeleteAlarm :: Text -> DeleteAlarm
newDeleteAlarm Text
pAlarmName_ =
  DeleteAlarm' {$sel:alarmName:DeleteAlarm' :: Text
alarmName = Text
pAlarmName_}

-- | The name of the alarm to delete.
deleteAlarm_alarmName :: Lens.Lens' DeleteAlarm Prelude.Text
deleteAlarm_alarmName :: Lens' DeleteAlarm Text
deleteAlarm_alarmName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteAlarm' {Text
alarmName :: Text
$sel:alarmName:DeleteAlarm' :: DeleteAlarm -> Text
alarmName} -> Text
alarmName) (\s :: DeleteAlarm
s@DeleteAlarm' {} Text
a -> DeleteAlarm
s {$sel:alarmName:DeleteAlarm' :: Text
alarmName = Text
a} :: DeleteAlarm)

instance Core.AWSRequest DeleteAlarm where
  type AWSResponse DeleteAlarm = DeleteAlarmResponse
  request :: (Service -> Service) -> DeleteAlarm -> Request DeleteAlarm
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 DeleteAlarm
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteAlarm)))
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 [Operation] -> Int -> DeleteAlarmResponse
DeleteAlarmResponse'
            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
"operations" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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 DeleteAlarm where
  hashWithSalt :: Int -> DeleteAlarm -> Int
hashWithSalt Int
_salt DeleteAlarm' {Text
alarmName :: Text
$sel:alarmName:DeleteAlarm' :: DeleteAlarm -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
alarmName

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

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

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

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

-- | /See:/ 'newDeleteAlarmResponse' smart constructor.
data DeleteAlarmResponse = DeleteAlarmResponse'
  { -- | An array of objects that describe the result of the action, such as the
    -- status of the request, the timestamp of the request, and the resources
    -- affected by the request.
    DeleteAlarmResponse -> Maybe [Operation]
operations :: Prelude.Maybe [Operation],
    -- | The response's http status code.
    DeleteAlarmResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteAlarmResponse -> DeleteAlarmResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteAlarmResponse -> DeleteAlarmResponse -> Bool
$c/= :: DeleteAlarmResponse -> DeleteAlarmResponse -> Bool
== :: DeleteAlarmResponse -> DeleteAlarmResponse -> Bool
$c== :: DeleteAlarmResponse -> DeleteAlarmResponse -> Bool
Prelude.Eq, ReadPrec [DeleteAlarmResponse]
ReadPrec DeleteAlarmResponse
Int -> ReadS DeleteAlarmResponse
ReadS [DeleteAlarmResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteAlarmResponse]
$creadListPrec :: ReadPrec [DeleteAlarmResponse]
readPrec :: ReadPrec DeleteAlarmResponse
$creadPrec :: ReadPrec DeleteAlarmResponse
readList :: ReadS [DeleteAlarmResponse]
$creadList :: ReadS [DeleteAlarmResponse]
readsPrec :: Int -> ReadS DeleteAlarmResponse
$creadsPrec :: Int -> ReadS DeleteAlarmResponse
Prelude.Read, Int -> DeleteAlarmResponse -> ShowS
[DeleteAlarmResponse] -> ShowS
DeleteAlarmResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteAlarmResponse] -> ShowS
$cshowList :: [DeleteAlarmResponse] -> ShowS
show :: DeleteAlarmResponse -> String
$cshow :: DeleteAlarmResponse -> String
showsPrec :: Int -> DeleteAlarmResponse -> ShowS
$cshowsPrec :: Int -> DeleteAlarmResponse -> ShowS
Prelude.Show, forall x. Rep DeleteAlarmResponse x -> DeleteAlarmResponse
forall x. DeleteAlarmResponse -> Rep DeleteAlarmResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteAlarmResponse x -> DeleteAlarmResponse
$cfrom :: forall x. DeleteAlarmResponse -> Rep DeleteAlarmResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteAlarmResponse' 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:
--
-- 'operations', 'deleteAlarmResponse_operations' - An array of objects that describe the result of the action, such as the
-- status of the request, the timestamp of the request, and the resources
-- affected by the request.
--
-- 'httpStatus', 'deleteAlarmResponse_httpStatus' - The response's http status code.
newDeleteAlarmResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteAlarmResponse
newDeleteAlarmResponse :: Int -> DeleteAlarmResponse
newDeleteAlarmResponse Int
pHttpStatus_ =
  DeleteAlarmResponse'
    { $sel:operations:DeleteAlarmResponse' :: Maybe [Operation]
operations = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteAlarmResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array of objects that describe the result of the action, such as the
-- status of the request, the timestamp of the request, and the resources
-- affected by the request.
deleteAlarmResponse_operations :: Lens.Lens' DeleteAlarmResponse (Prelude.Maybe [Operation])
deleteAlarmResponse_operations :: Lens' DeleteAlarmResponse (Maybe [Operation])
deleteAlarmResponse_operations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteAlarmResponse' {Maybe [Operation]
operations :: Maybe [Operation]
$sel:operations:DeleteAlarmResponse' :: DeleteAlarmResponse -> Maybe [Operation]
operations} -> Maybe [Operation]
operations) (\s :: DeleteAlarmResponse
s@DeleteAlarmResponse' {} Maybe [Operation]
a -> DeleteAlarmResponse
s {$sel:operations:DeleteAlarmResponse' :: Maybe [Operation]
operations = Maybe [Operation]
a} :: DeleteAlarmResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.NFData DeleteAlarmResponse where
  rnf :: DeleteAlarmResponse -> ()
rnf DeleteAlarmResponse' {Int
Maybe [Operation]
httpStatus :: Int
operations :: Maybe [Operation]
$sel:httpStatus:DeleteAlarmResponse' :: DeleteAlarmResponse -> Int
$sel:operations:DeleteAlarmResponse' :: DeleteAlarmResponse -> Maybe [Operation]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Operation]
operations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus