{-# 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.GetAlarms
-- 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 information about the configured alarms. Specify an alarm name
-- in your request to return information about a specific alarm, or specify
-- a monitored resource name to return information about all alarms for a
-- specific resource.
--
-- 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.GetAlarms
  ( -- * Creating a Request
    GetAlarms (..),
    newGetAlarms,

    -- * Request Lenses
    getAlarms_alarmName,
    getAlarms_monitoredResourceName,
    getAlarms_pageToken,

    -- * Destructuring the Response
    GetAlarmsResponse (..),
    newGetAlarmsResponse,

    -- * Response Lenses
    getAlarmsResponse_alarms,
    getAlarmsResponse_nextPageToken,
    getAlarmsResponse_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:/ 'newGetAlarms' smart constructor.
data GetAlarms = GetAlarms'
  { -- | The name of the alarm.
    --
    -- Specify an alarm name to return information about a specific alarm.
    GetAlarms -> Maybe Text
alarmName :: Prelude.Maybe Prelude.Text,
    -- | The name of the Lightsail resource being monitored by the alarm.
    --
    -- Specify a monitored resource name to return information about all alarms
    -- for a specific resource.
    GetAlarms -> Maybe Text
monitoredResourceName :: Prelude.Maybe Prelude.Text,
    -- | The token to advance to the next page of results from your request.
    --
    -- To get a page token, perform an initial @GetAlarms@ request. If your
    -- results are paginated, the response will return a next page token that
    -- you can specify as the page token in a subsequent request.
    GetAlarms -> Maybe Text
pageToken :: Prelude.Maybe Prelude.Text
  }
  deriving (GetAlarms -> GetAlarms -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAlarms -> GetAlarms -> Bool
$c/= :: GetAlarms -> GetAlarms -> Bool
== :: GetAlarms -> GetAlarms -> Bool
$c== :: GetAlarms -> GetAlarms -> Bool
Prelude.Eq, ReadPrec [GetAlarms]
ReadPrec GetAlarms
Int -> ReadS GetAlarms
ReadS [GetAlarms]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetAlarms]
$creadListPrec :: ReadPrec [GetAlarms]
readPrec :: ReadPrec GetAlarms
$creadPrec :: ReadPrec GetAlarms
readList :: ReadS [GetAlarms]
$creadList :: ReadS [GetAlarms]
readsPrec :: Int -> ReadS GetAlarms
$creadsPrec :: Int -> ReadS GetAlarms
Prelude.Read, Int -> GetAlarms -> ShowS
[GetAlarms] -> ShowS
GetAlarms -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAlarms] -> ShowS
$cshowList :: [GetAlarms] -> ShowS
show :: GetAlarms -> String
$cshow :: GetAlarms -> String
showsPrec :: Int -> GetAlarms -> ShowS
$cshowsPrec :: Int -> GetAlarms -> ShowS
Prelude.Show, forall x. Rep GetAlarms x -> GetAlarms
forall x. GetAlarms -> Rep GetAlarms x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetAlarms x -> GetAlarms
$cfrom :: forall x. GetAlarms -> Rep GetAlarms x
Prelude.Generic)

-- |
-- Create a value of 'GetAlarms' 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', 'getAlarms_alarmName' - The name of the alarm.
--
-- Specify an alarm name to return information about a specific alarm.
--
-- 'monitoredResourceName', 'getAlarms_monitoredResourceName' - The name of the Lightsail resource being monitored by the alarm.
--
-- Specify a monitored resource name to return information about all alarms
-- for a specific resource.
--
-- 'pageToken', 'getAlarms_pageToken' - The token to advance to the next page of results from your request.
--
-- To get a page token, perform an initial @GetAlarms@ request. If your
-- results are paginated, the response will return a next page token that
-- you can specify as the page token in a subsequent request.
newGetAlarms ::
  GetAlarms
newGetAlarms :: GetAlarms
newGetAlarms =
  GetAlarms'
    { $sel:alarmName:GetAlarms' :: Maybe Text
alarmName = forall a. Maybe a
Prelude.Nothing,
      $sel:monitoredResourceName:GetAlarms' :: Maybe Text
monitoredResourceName = forall a. Maybe a
Prelude.Nothing,
      $sel:pageToken:GetAlarms' :: Maybe Text
pageToken = forall a. Maybe a
Prelude.Nothing
    }

-- | The name of the alarm.
--
-- Specify an alarm name to return information about a specific alarm.
getAlarms_alarmName :: Lens.Lens' GetAlarms (Prelude.Maybe Prelude.Text)
getAlarms_alarmName :: Lens' GetAlarms (Maybe Text)
getAlarms_alarmName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAlarms' {Maybe Text
alarmName :: Maybe Text
$sel:alarmName:GetAlarms' :: GetAlarms -> Maybe Text
alarmName} -> Maybe Text
alarmName) (\s :: GetAlarms
s@GetAlarms' {} Maybe Text
a -> GetAlarms
s {$sel:alarmName:GetAlarms' :: Maybe Text
alarmName = Maybe Text
a} :: GetAlarms)

-- | The name of the Lightsail resource being monitored by the alarm.
--
-- Specify a monitored resource name to return information about all alarms
-- for a specific resource.
getAlarms_monitoredResourceName :: Lens.Lens' GetAlarms (Prelude.Maybe Prelude.Text)
getAlarms_monitoredResourceName :: Lens' GetAlarms (Maybe Text)
getAlarms_monitoredResourceName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAlarms' {Maybe Text
monitoredResourceName :: Maybe Text
$sel:monitoredResourceName:GetAlarms' :: GetAlarms -> Maybe Text
monitoredResourceName} -> Maybe Text
monitoredResourceName) (\s :: GetAlarms
s@GetAlarms' {} Maybe Text
a -> GetAlarms
s {$sel:monitoredResourceName:GetAlarms' :: Maybe Text
monitoredResourceName = Maybe Text
a} :: GetAlarms)

-- | The token to advance to the next page of results from your request.
--
-- To get a page token, perform an initial @GetAlarms@ request. If your
-- results are paginated, the response will return a next page token that
-- you can specify as the page token in a subsequent request.
getAlarms_pageToken :: Lens.Lens' GetAlarms (Prelude.Maybe Prelude.Text)
getAlarms_pageToken :: Lens' GetAlarms (Maybe Text)
getAlarms_pageToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAlarms' {Maybe Text
pageToken :: Maybe Text
$sel:pageToken:GetAlarms' :: GetAlarms -> Maybe Text
pageToken} -> Maybe Text
pageToken) (\s :: GetAlarms
s@GetAlarms' {} Maybe Text
a -> GetAlarms
s {$sel:pageToken:GetAlarms' :: Maybe Text
pageToken = Maybe Text
a} :: GetAlarms)

instance Core.AWSRequest GetAlarms where
  type AWSResponse GetAlarms = GetAlarmsResponse
  request :: (Service -> Service) -> GetAlarms -> Request GetAlarms
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 GetAlarms
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetAlarms)))
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 [Alarm] -> Maybe Text -> Int -> GetAlarmsResponse
GetAlarmsResponse'
            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
"alarms" 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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"nextPageToken")
            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 GetAlarms where
  hashWithSalt :: Int -> GetAlarms -> Int
hashWithSalt Int
_salt GetAlarms' {Maybe Text
pageToken :: Maybe Text
monitoredResourceName :: Maybe Text
alarmName :: Maybe Text
$sel:pageToken:GetAlarms' :: GetAlarms -> Maybe Text
$sel:monitoredResourceName:GetAlarms' :: GetAlarms -> Maybe Text
$sel:alarmName:GetAlarms' :: GetAlarms -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
alarmName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
monitoredResourceName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
pageToken

instance Prelude.NFData GetAlarms where
  rnf :: GetAlarms -> ()
rnf GetAlarms' {Maybe Text
pageToken :: Maybe Text
monitoredResourceName :: Maybe Text
alarmName :: Maybe Text
$sel:pageToken:GetAlarms' :: GetAlarms -> Maybe Text
$sel:monitoredResourceName:GetAlarms' :: GetAlarms -> Maybe Text
$sel:alarmName:GetAlarms' :: GetAlarms -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
alarmName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
monitoredResourceName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
pageToken

instance Data.ToHeaders GetAlarms where
  toHeaders :: GetAlarms -> 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.GetAlarms" ::
                          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 GetAlarms where
  toJSON :: GetAlarms -> Value
toJSON GetAlarms' {Maybe Text
pageToken :: Maybe Text
monitoredResourceName :: Maybe Text
alarmName :: Maybe Text
$sel:pageToken:GetAlarms' :: GetAlarms -> Maybe Text
$sel:monitoredResourceName:GetAlarms' :: GetAlarms -> Maybe Text
$sel:alarmName:GetAlarms' :: GetAlarms -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"alarmName" 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
alarmName,
            (Key
"monitoredResourceName" 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
monitoredResourceName,
            (Key
"pageToken" 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
pageToken
          ]
      )

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

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

-- | /See:/ 'newGetAlarmsResponse' smart constructor.
data GetAlarmsResponse = GetAlarmsResponse'
  { -- | An array of objects that describe the alarms.
    GetAlarmsResponse -> Maybe [Alarm]
alarms :: Prelude.Maybe [Alarm],
    -- | The token to advance to the next page of results from your request.
    --
    -- A next page token is not returned if there are no more results to
    -- display.
    --
    -- To get the next page of results, perform another @GetAlarms@ request and
    -- specify the next page token using the @pageToken@ parameter.
    GetAlarmsResponse -> Maybe Text
nextPageToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetAlarmsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetAlarmsResponse -> GetAlarmsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAlarmsResponse -> GetAlarmsResponse -> Bool
$c/= :: GetAlarmsResponse -> GetAlarmsResponse -> Bool
== :: GetAlarmsResponse -> GetAlarmsResponse -> Bool
$c== :: GetAlarmsResponse -> GetAlarmsResponse -> Bool
Prelude.Eq, ReadPrec [GetAlarmsResponse]
ReadPrec GetAlarmsResponse
Int -> ReadS GetAlarmsResponse
ReadS [GetAlarmsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetAlarmsResponse]
$creadListPrec :: ReadPrec [GetAlarmsResponse]
readPrec :: ReadPrec GetAlarmsResponse
$creadPrec :: ReadPrec GetAlarmsResponse
readList :: ReadS [GetAlarmsResponse]
$creadList :: ReadS [GetAlarmsResponse]
readsPrec :: Int -> ReadS GetAlarmsResponse
$creadsPrec :: Int -> ReadS GetAlarmsResponse
Prelude.Read, Int -> GetAlarmsResponse -> ShowS
[GetAlarmsResponse] -> ShowS
GetAlarmsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAlarmsResponse] -> ShowS
$cshowList :: [GetAlarmsResponse] -> ShowS
show :: GetAlarmsResponse -> String
$cshow :: GetAlarmsResponse -> String
showsPrec :: Int -> GetAlarmsResponse -> ShowS
$cshowsPrec :: Int -> GetAlarmsResponse -> ShowS
Prelude.Show, forall x. Rep GetAlarmsResponse x -> GetAlarmsResponse
forall x. GetAlarmsResponse -> Rep GetAlarmsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetAlarmsResponse x -> GetAlarmsResponse
$cfrom :: forall x. GetAlarmsResponse -> Rep GetAlarmsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetAlarmsResponse' 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:
--
-- 'alarms', 'getAlarmsResponse_alarms' - An array of objects that describe the alarms.
--
-- 'nextPageToken', 'getAlarmsResponse_nextPageToken' - The token to advance to the next page of results from your request.
--
-- A next page token is not returned if there are no more results to
-- display.
--
-- To get the next page of results, perform another @GetAlarms@ request and
-- specify the next page token using the @pageToken@ parameter.
--
-- 'httpStatus', 'getAlarmsResponse_httpStatus' - The response's http status code.
newGetAlarmsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetAlarmsResponse
newGetAlarmsResponse :: Int -> GetAlarmsResponse
newGetAlarmsResponse Int
pHttpStatus_ =
  GetAlarmsResponse'
    { $sel:alarms:GetAlarmsResponse' :: Maybe [Alarm]
alarms = forall a. Maybe a
Prelude.Nothing,
      $sel:nextPageToken:GetAlarmsResponse' :: Maybe Text
nextPageToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetAlarmsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array of objects that describe the alarms.
getAlarmsResponse_alarms :: Lens.Lens' GetAlarmsResponse (Prelude.Maybe [Alarm])
getAlarmsResponse_alarms :: Lens' GetAlarmsResponse (Maybe [Alarm])
getAlarmsResponse_alarms = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAlarmsResponse' {Maybe [Alarm]
alarms :: Maybe [Alarm]
$sel:alarms:GetAlarmsResponse' :: GetAlarmsResponse -> Maybe [Alarm]
alarms} -> Maybe [Alarm]
alarms) (\s :: GetAlarmsResponse
s@GetAlarmsResponse' {} Maybe [Alarm]
a -> GetAlarmsResponse
s {$sel:alarms:GetAlarmsResponse' :: Maybe [Alarm]
alarms = Maybe [Alarm]
a} :: GetAlarmsResponse) 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 token to advance to the next page of results from your request.
--
-- A next page token is not returned if there are no more results to
-- display.
--
-- To get the next page of results, perform another @GetAlarms@ request and
-- specify the next page token using the @pageToken@ parameter.
getAlarmsResponse_nextPageToken :: Lens.Lens' GetAlarmsResponse (Prelude.Maybe Prelude.Text)
getAlarmsResponse_nextPageToken :: Lens' GetAlarmsResponse (Maybe Text)
getAlarmsResponse_nextPageToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAlarmsResponse' {Maybe Text
nextPageToken :: Maybe Text
$sel:nextPageToken:GetAlarmsResponse' :: GetAlarmsResponse -> Maybe Text
nextPageToken} -> Maybe Text
nextPageToken) (\s :: GetAlarmsResponse
s@GetAlarmsResponse' {} Maybe Text
a -> GetAlarmsResponse
s {$sel:nextPageToken:GetAlarmsResponse' :: Maybe Text
nextPageToken = Maybe Text
a} :: GetAlarmsResponse)

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

instance Prelude.NFData GetAlarmsResponse where
  rnf :: GetAlarmsResponse -> ()
rnf GetAlarmsResponse' {Int
Maybe [Alarm]
Maybe Text
httpStatus :: Int
nextPageToken :: Maybe Text
alarms :: Maybe [Alarm]
$sel:httpStatus:GetAlarmsResponse' :: GetAlarmsResponse -> Int
$sel:nextPageToken:GetAlarmsResponse' :: GetAlarmsResponse -> Maybe Text
$sel:alarms:GetAlarmsResponse' :: GetAlarmsResponse -> Maybe [Alarm]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Alarm]
alarms
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextPageToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus