{-# 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.Route53.GetHealthCheckStatus
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets status of a specified health check.
--
-- This API is intended for use during development to diagnose behavior. It
-- doesn’t support production use-cases with high query rates that require
-- immediate and actionable responses.
module Amazonka.Route53.GetHealthCheckStatus
  ( -- * Creating a Request
    GetHealthCheckStatus (..),
    newGetHealthCheckStatus,

    -- * Request Lenses
    getHealthCheckStatus_healthCheckId,

    -- * Destructuring the Response
    GetHealthCheckStatusResponse (..),
    newGetHealthCheckStatusResponse,

    -- * Response Lenses
    getHealthCheckStatusResponse_httpStatus,
    getHealthCheckStatusResponse_healthCheckObservations,
  )
where

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

-- | A request to get the status for a health check.
--
-- /See:/ 'newGetHealthCheckStatus' smart constructor.
data GetHealthCheckStatus = GetHealthCheckStatus'
  { -- | The ID for the health check that you want the current status for. When
    -- you created the health check, @CreateHealthCheck@ returned the ID in the
    -- response, in the @HealthCheckId@ element.
    --
    -- If you want to check the status of a calculated health check, you must
    -- use the Amazon Route 53 console or the CloudWatch console. You can\'t
    -- use @GetHealthCheckStatus@ to get the status of a calculated health
    -- check.
    GetHealthCheckStatus -> Text
healthCheckId :: Prelude.Text
  }
  deriving (GetHealthCheckStatus -> GetHealthCheckStatus -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetHealthCheckStatus -> GetHealthCheckStatus -> Bool
$c/= :: GetHealthCheckStatus -> GetHealthCheckStatus -> Bool
== :: GetHealthCheckStatus -> GetHealthCheckStatus -> Bool
$c== :: GetHealthCheckStatus -> GetHealthCheckStatus -> Bool
Prelude.Eq, ReadPrec [GetHealthCheckStatus]
ReadPrec GetHealthCheckStatus
Int -> ReadS GetHealthCheckStatus
ReadS [GetHealthCheckStatus]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetHealthCheckStatus]
$creadListPrec :: ReadPrec [GetHealthCheckStatus]
readPrec :: ReadPrec GetHealthCheckStatus
$creadPrec :: ReadPrec GetHealthCheckStatus
readList :: ReadS [GetHealthCheckStatus]
$creadList :: ReadS [GetHealthCheckStatus]
readsPrec :: Int -> ReadS GetHealthCheckStatus
$creadsPrec :: Int -> ReadS GetHealthCheckStatus
Prelude.Read, Int -> GetHealthCheckStatus -> ShowS
[GetHealthCheckStatus] -> ShowS
GetHealthCheckStatus -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetHealthCheckStatus] -> ShowS
$cshowList :: [GetHealthCheckStatus] -> ShowS
show :: GetHealthCheckStatus -> String
$cshow :: GetHealthCheckStatus -> String
showsPrec :: Int -> GetHealthCheckStatus -> ShowS
$cshowsPrec :: Int -> GetHealthCheckStatus -> ShowS
Prelude.Show, forall x. Rep GetHealthCheckStatus x -> GetHealthCheckStatus
forall x. GetHealthCheckStatus -> Rep GetHealthCheckStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetHealthCheckStatus x -> GetHealthCheckStatus
$cfrom :: forall x. GetHealthCheckStatus -> Rep GetHealthCheckStatus x
Prelude.Generic)

-- |
-- Create a value of 'GetHealthCheckStatus' 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:
--
-- 'healthCheckId', 'getHealthCheckStatus_healthCheckId' - The ID for the health check that you want the current status for. When
-- you created the health check, @CreateHealthCheck@ returned the ID in the
-- response, in the @HealthCheckId@ element.
--
-- If you want to check the status of a calculated health check, you must
-- use the Amazon Route 53 console or the CloudWatch console. You can\'t
-- use @GetHealthCheckStatus@ to get the status of a calculated health
-- check.
newGetHealthCheckStatus ::
  -- | 'healthCheckId'
  Prelude.Text ->
  GetHealthCheckStatus
newGetHealthCheckStatus :: Text -> GetHealthCheckStatus
newGetHealthCheckStatus Text
pHealthCheckId_ =
  GetHealthCheckStatus'
    { $sel:healthCheckId:GetHealthCheckStatus' :: Text
healthCheckId =
        Text
pHealthCheckId_
    }

-- | The ID for the health check that you want the current status for. When
-- you created the health check, @CreateHealthCheck@ returned the ID in the
-- response, in the @HealthCheckId@ element.
--
-- If you want to check the status of a calculated health check, you must
-- use the Amazon Route 53 console or the CloudWatch console. You can\'t
-- use @GetHealthCheckStatus@ to get the status of a calculated health
-- check.
getHealthCheckStatus_healthCheckId :: Lens.Lens' GetHealthCheckStatus Prelude.Text
getHealthCheckStatus_healthCheckId :: Lens' GetHealthCheckStatus Text
getHealthCheckStatus_healthCheckId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetHealthCheckStatus' {Text
healthCheckId :: Text
$sel:healthCheckId:GetHealthCheckStatus' :: GetHealthCheckStatus -> Text
healthCheckId} -> Text
healthCheckId) (\s :: GetHealthCheckStatus
s@GetHealthCheckStatus' {} Text
a -> GetHealthCheckStatus
s {$sel:healthCheckId:GetHealthCheckStatus' :: Text
healthCheckId = Text
a} :: GetHealthCheckStatus)

instance Core.AWSRequest GetHealthCheckStatus where
  type
    AWSResponse GetHealthCheckStatus =
      GetHealthCheckStatusResponse
  request :: (Service -> Service)
-> GetHealthCheckStatus -> Request GetHealthCheckStatus
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetHealthCheckStatus
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetHealthCheckStatus)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int -> [HealthCheckObservation] -> GetHealthCheckStatusResponse
GetHealthCheckStatusResponse'
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                            forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"HealthCheckObservations"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"HealthCheckObservation"
                        )
      )

instance Prelude.Hashable GetHealthCheckStatus where
  hashWithSalt :: Int -> GetHealthCheckStatus -> Int
hashWithSalt Int
_salt GetHealthCheckStatus' {Text
healthCheckId :: Text
$sel:healthCheckId:GetHealthCheckStatus' :: GetHealthCheckStatus -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
healthCheckId

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

instance Data.ToHeaders GetHealthCheckStatus where
  toHeaders :: GetHealthCheckStatus -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath GetHealthCheckStatus where
  toPath :: GetHealthCheckStatus -> ByteString
toPath GetHealthCheckStatus' {Text
healthCheckId :: Text
$sel:healthCheckId:GetHealthCheckStatus' :: GetHealthCheckStatus -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/2013-04-01/healthcheck/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
healthCheckId,
        ByteString
"/status"
      ]

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

-- | A complex type that contains the response to a @GetHealthCheck@ request.
--
-- /See:/ 'newGetHealthCheckStatusResponse' smart constructor.
data GetHealthCheckStatusResponse = GetHealthCheckStatusResponse'
  { -- | The response's http status code.
    GetHealthCheckStatusResponse -> Int
httpStatus :: Prelude.Int,
    -- | A list that contains one @HealthCheckObservation@ element for each
    -- Amazon Route 53 health checker that is reporting a status about the
    -- health check endpoint.
    GetHealthCheckStatusResponse -> [HealthCheckObservation]
healthCheckObservations :: [HealthCheckObservation]
  }
  deriving (GetHealthCheckStatusResponse
-> GetHealthCheckStatusResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetHealthCheckStatusResponse
-> GetHealthCheckStatusResponse -> Bool
$c/= :: GetHealthCheckStatusResponse
-> GetHealthCheckStatusResponse -> Bool
== :: GetHealthCheckStatusResponse
-> GetHealthCheckStatusResponse -> Bool
$c== :: GetHealthCheckStatusResponse
-> GetHealthCheckStatusResponse -> Bool
Prelude.Eq, ReadPrec [GetHealthCheckStatusResponse]
ReadPrec GetHealthCheckStatusResponse
Int -> ReadS GetHealthCheckStatusResponse
ReadS [GetHealthCheckStatusResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetHealthCheckStatusResponse]
$creadListPrec :: ReadPrec [GetHealthCheckStatusResponse]
readPrec :: ReadPrec GetHealthCheckStatusResponse
$creadPrec :: ReadPrec GetHealthCheckStatusResponse
readList :: ReadS [GetHealthCheckStatusResponse]
$creadList :: ReadS [GetHealthCheckStatusResponse]
readsPrec :: Int -> ReadS GetHealthCheckStatusResponse
$creadsPrec :: Int -> ReadS GetHealthCheckStatusResponse
Prelude.Read, Int -> GetHealthCheckStatusResponse -> ShowS
[GetHealthCheckStatusResponse] -> ShowS
GetHealthCheckStatusResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetHealthCheckStatusResponse] -> ShowS
$cshowList :: [GetHealthCheckStatusResponse] -> ShowS
show :: GetHealthCheckStatusResponse -> String
$cshow :: GetHealthCheckStatusResponse -> String
showsPrec :: Int -> GetHealthCheckStatusResponse -> ShowS
$cshowsPrec :: Int -> GetHealthCheckStatusResponse -> ShowS
Prelude.Show, forall x.
Rep GetHealthCheckStatusResponse x -> GetHealthCheckStatusResponse
forall x.
GetHealthCheckStatusResponse -> Rep GetHealthCheckStatusResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetHealthCheckStatusResponse x -> GetHealthCheckStatusResponse
$cfrom :: forall x.
GetHealthCheckStatusResponse -> Rep GetHealthCheckStatusResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetHealthCheckStatusResponse' 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', 'getHealthCheckStatusResponse_httpStatus' - The response's http status code.
--
-- 'healthCheckObservations', 'getHealthCheckStatusResponse_healthCheckObservations' - A list that contains one @HealthCheckObservation@ element for each
-- Amazon Route 53 health checker that is reporting a status about the
-- health check endpoint.
newGetHealthCheckStatusResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetHealthCheckStatusResponse
newGetHealthCheckStatusResponse :: Int -> GetHealthCheckStatusResponse
newGetHealthCheckStatusResponse Int
pHttpStatus_ =
  GetHealthCheckStatusResponse'
    { $sel:httpStatus:GetHealthCheckStatusResponse' :: Int
httpStatus =
        Int
pHttpStatus_,
      $sel:healthCheckObservations:GetHealthCheckStatusResponse' :: [HealthCheckObservation]
healthCheckObservations = forall a. Monoid a => a
Prelude.mempty
    }

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

-- | A list that contains one @HealthCheckObservation@ element for each
-- Amazon Route 53 health checker that is reporting a status about the
-- health check endpoint.
getHealthCheckStatusResponse_healthCheckObservations :: Lens.Lens' GetHealthCheckStatusResponse [HealthCheckObservation]
getHealthCheckStatusResponse_healthCheckObservations :: Lens' GetHealthCheckStatusResponse [HealthCheckObservation]
getHealthCheckStatusResponse_healthCheckObservations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetHealthCheckStatusResponse' {[HealthCheckObservation]
healthCheckObservations :: [HealthCheckObservation]
$sel:healthCheckObservations:GetHealthCheckStatusResponse' :: GetHealthCheckStatusResponse -> [HealthCheckObservation]
healthCheckObservations} -> [HealthCheckObservation]
healthCheckObservations) (\s :: GetHealthCheckStatusResponse
s@GetHealthCheckStatusResponse' {} [HealthCheckObservation]
a -> GetHealthCheckStatusResponse
s {$sel:healthCheckObservations:GetHealthCheckStatusResponse' :: [HealthCheckObservation]
healthCheckObservations = [HealthCheckObservation]
a} :: GetHealthCheckStatusResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Prelude.NFData GetHealthCheckStatusResponse where
  rnf :: GetHealthCheckStatusResponse -> ()
rnf GetHealthCheckStatusResponse' {Int
[HealthCheckObservation]
healthCheckObservations :: [HealthCheckObservation]
httpStatus :: Int
$sel:healthCheckObservations:GetHealthCheckStatusResponse' :: GetHealthCheckStatusResponse -> [HealthCheckObservation]
$sel:httpStatus:GetHealthCheckStatusResponse' :: GetHealthCheckStatusResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [HealthCheckObservation]
healthCheckObservations