{-# 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.Route53RecoveryReadiness.GetReadinessCheck
-- 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 details about a readiness check.
module Amazonka.Route53RecoveryReadiness.GetReadinessCheck
  ( -- * Creating a Request
    GetReadinessCheck (..),
    newGetReadinessCheck,

    -- * Request Lenses
    getReadinessCheck_readinessCheckName,

    -- * Destructuring the Response
    GetReadinessCheckResponse (..),
    newGetReadinessCheckResponse,

    -- * Response Lenses
    getReadinessCheckResponse_readinessCheckArn,
    getReadinessCheckResponse_readinessCheckName,
    getReadinessCheckResponse_resourceSet,
    getReadinessCheckResponse_tags,
    getReadinessCheckResponse_httpStatus,
  )
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.Route53RecoveryReadiness.Types

-- | /See:/ 'newGetReadinessCheck' smart constructor.
data GetReadinessCheck = GetReadinessCheck'
  { -- | Name of a readiness check.
    GetReadinessCheck -> Text
readinessCheckName :: Prelude.Text
  }
  deriving (GetReadinessCheck -> GetReadinessCheck -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetReadinessCheck -> GetReadinessCheck -> Bool
$c/= :: GetReadinessCheck -> GetReadinessCheck -> Bool
== :: GetReadinessCheck -> GetReadinessCheck -> Bool
$c== :: GetReadinessCheck -> GetReadinessCheck -> Bool
Prelude.Eq, ReadPrec [GetReadinessCheck]
ReadPrec GetReadinessCheck
Int -> ReadS GetReadinessCheck
ReadS [GetReadinessCheck]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetReadinessCheck]
$creadListPrec :: ReadPrec [GetReadinessCheck]
readPrec :: ReadPrec GetReadinessCheck
$creadPrec :: ReadPrec GetReadinessCheck
readList :: ReadS [GetReadinessCheck]
$creadList :: ReadS [GetReadinessCheck]
readsPrec :: Int -> ReadS GetReadinessCheck
$creadsPrec :: Int -> ReadS GetReadinessCheck
Prelude.Read, Int -> GetReadinessCheck -> ShowS
[GetReadinessCheck] -> ShowS
GetReadinessCheck -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetReadinessCheck] -> ShowS
$cshowList :: [GetReadinessCheck] -> ShowS
show :: GetReadinessCheck -> String
$cshow :: GetReadinessCheck -> String
showsPrec :: Int -> GetReadinessCheck -> ShowS
$cshowsPrec :: Int -> GetReadinessCheck -> ShowS
Prelude.Show, forall x. Rep GetReadinessCheck x -> GetReadinessCheck
forall x. GetReadinessCheck -> Rep GetReadinessCheck x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetReadinessCheck x -> GetReadinessCheck
$cfrom :: forall x. GetReadinessCheck -> Rep GetReadinessCheck x
Prelude.Generic)

-- |
-- Create a value of 'GetReadinessCheck' 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:
--
-- 'readinessCheckName', 'getReadinessCheck_readinessCheckName' - Name of a readiness check.
newGetReadinessCheck ::
  -- | 'readinessCheckName'
  Prelude.Text ->
  GetReadinessCheck
newGetReadinessCheck :: Text -> GetReadinessCheck
newGetReadinessCheck Text
pReadinessCheckName_ =
  GetReadinessCheck'
    { $sel:readinessCheckName:GetReadinessCheck' :: Text
readinessCheckName =
        Text
pReadinessCheckName_
    }

-- | Name of a readiness check.
getReadinessCheck_readinessCheckName :: Lens.Lens' GetReadinessCheck Prelude.Text
getReadinessCheck_readinessCheckName :: Lens' GetReadinessCheck Text
getReadinessCheck_readinessCheckName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetReadinessCheck' {Text
readinessCheckName :: Text
$sel:readinessCheckName:GetReadinessCheck' :: GetReadinessCheck -> Text
readinessCheckName} -> Text
readinessCheckName) (\s :: GetReadinessCheck
s@GetReadinessCheck' {} Text
a -> GetReadinessCheck
s {$sel:readinessCheckName:GetReadinessCheck' :: Text
readinessCheckName = Text
a} :: GetReadinessCheck)

instance Core.AWSRequest GetReadinessCheck where
  type
    AWSResponse GetReadinessCheck =
      GetReadinessCheckResponse
  request :: (Service -> Service)
-> GetReadinessCheck -> Request GetReadinessCheck
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 GetReadinessCheck
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetReadinessCheck)))
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 Text
-> Maybe Text
-> Maybe Text
-> Maybe (HashMap Text Text)
-> Int
-> GetReadinessCheckResponse
GetReadinessCheckResponse'
            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
"readinessCheckArn")
            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
"readinessCheckName")
            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
"resourceSet")
            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
"tags" 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 GetReadinessCheck where
  hashWithSalt :: Int -> GetReadinessCheck -> Int
hashWithSalt Int
_salt GetReadinessCheck' {Text
readinessCheckName :: Text
$sel:readinessCheckName:GetReadinessCheck' :: GetReadinessCheck -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
readinessCheckName

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

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

instance Data.ToPath GetReadinessCheck where
  toPath :: GetReadinessCheck -> ByteString
toPath GetReadinessCheck' {Text
readinessCheckName :: Text
$sel:readinessCheckName:GetReadinessCheck' :: GetReadinessCheck -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/readinesschecks/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
readinessCheckName]

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

-- | /See:/ 'newGetReadinessCheckResponse' smart constructor.
data GetReadinessCheckResponse = GetReadinessCheckResponse'
  { -- | The Amazon Resource Name (ARN) associated with a readiness check.
    GetReadinessCheckResponse -> Maybe Text
readinessCheckArn :: Prelude.Maybe Prelude.Text,
    -- | Name of a readiness check.
    GetReadinessCheckResponse -> Maybe Text
readinessCheckName :: Prelude.Maybe Prelude.Text,
    -- | Name of the resource set to be checked.
    GetReadinessCheckResponse -> Maybe Text
resourceSet :: Prelude.Maybe Prelude.Text,
    GetReadinessCheckResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The response's http status code.
    GetReadinessCheckResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetReadinessCheckResponse -> GetReadinessCheckResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetReadinessCheckResponse -> GetReadinessCheckResponse -> Bool
$c/= :: GetReadinessCheckResponse -> GetReadinessCheckResponse -> Bool
== :: GetReadinessCheckResponse -> GetReadinessCheckResponse -> Bool
$c== :: GetReadinessCheckResponse -> GetReadinessCheckResponse -> Bool
Prelude.Eq, ReadPrec [GetReadinessCheckResponse]
ReadPrec GetReadinessCheckResponse
Int -> ReadS GetReadinessCheckResponse
ReadS [GetReadinessCheckResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetReadinessCheckResponse]
$creadListPrec :: ReadPrec [GetReadinessCheckResponse]
readPrec :: ReadPrec GetReadinessCheckResponse
$creadPrec :: ReadPrec GetReadinessCheckResponse
readList :: ReadS [GetReadinessCheckResponse]
$creadList :: ReadS [GetReadinessCheckResponse]
readsPrec :: Int -> ReadS GetReadinessCheckResponse
$creadsPrec :: Int -> ReadS GetReadinessCheckResponse
Prelude.Read, Int -> GetReadinessCheckResponse -> ShowS
[GetReadinessCheckResponse] -> ShowS
GetReadinessCheckResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetReadinessCheckResponse] -> ShowS
$cshowList :: [GetReadinessCheckResponse] -> ShowS
show :: GetReadinessCheckResponse -> String
$cshow :: GetReadinessCheckResponse -> String
showsPrec :: Int -> GetReadinessCheckResponse -> ShowS
$cshowsPrec :: Int -> GetReadinessCheckResponse -> ShowS
Prelude.Show, forall x.
Rep GetReadinessCheckResponse x -> GetReadinessCheckResponse
forall x.
GetReadinessCheckResponse -> Rep GetReadinessCheckResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetReadinessCheckResponse x -> GetReadinessCheckResponse
$cfrom :: forall x.
GetReadinessCheckResponse -> Rep GetReadinessCheckResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetReadinessCheckResponse' 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:
--
-- 'readinessCheckArn', 'getReadinessCheckResponse_readinessCheckArn' - The Amazon Resource Name (ARN) associated with a readiness check.
--
-- 'readinessCheckName', 'getReadinessCheckResponse_readinessCheckName' - Name of a readiness check.
--
-- 'resourceSet', 'getReadinessCheckResponse_resourceSet' - Name of the resource set to be checked.
--
-- 'tags', 'getReadinessCheckResponse_tags' - Undocumented member.
--
-- 'httpStatus', 'getReadinessCheckResponse_httpStatus' - The response's http status code.
newGetReadinessCheckResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetReadinessCheckResponse
newGetReadinessCheckResponse :: Int -> GetReadinessCheckResponse
newGetReadinessCheckResponse Int
pHttpStatus_ =
  GetReadinessCheckResponse'
    { $sel:readinessCheckArn:GetReadinessCheckResponse' :: Maybe Text
readinessCheckArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:readinessCheckName:GetReadinessCheckResponse' :: Maybe Text
readinessCheckName = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceSet:GetReadinessCheckResponse' :: Maybe Text
resourceSet = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:GetReadinessCheckResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetReadinessCheckResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) associated with a readiness check.
getReadinessCheckResponse_readinessCheckArn :: Lens.Lens' GetReadinessCheckResponse (Prelude.Maybe Prelude.Text)
getReadinessCheckResponse_readinessCheckArn :: Lens' GetReadinessCheckResponse (Maybe Text)
getReadinessCheckResponse_readinessCheckArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetReadinessCheckResponse' {Maybe Text
readinessCheckArn :: Maybe Text
$sel:readinessCheckArn:GetReadinessCheckResponse' :: GetReadinessCheckResponse -> Maybe Text
readinessCheckArn} -> Maybe Text
readinessCheckArn) (\s :: GetReadinessCheckResponse
s@GetReadinessCheckResponse' {} Maybe Text
a -> GetReadinessCheckResponse
s {$sel:readinessCheckArn:GetReadinessCheckResponse' :: Maybe Text
readinessCheckArn = Maybe Text
a} :: GetReadinessCheckResponse)

-- | Name of a readiness check.
getReadinessCheckResponse_readinessCheckName :: Lens.Lens' GetReadinessCheckResponse (Prelude.Maybe Prelude.Text)
getReadinessCheckResponse_readinessCheckName :: Lens' GetReadinessCheckResponse (Maybe Text)
getReadinessCheckResponse_readinessCheckName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetReadinessCheckResponse' {Maybe Text
readinessCheckName :: Maybe Text
$sel:readinessCheckName:GetReadinessCheckResponse' :: GetReadinessCheckResponse -> Maybe Text
readinessCheckName} -> Maybe Text
readinessCheckName) (\s :: GetReadinessCheckResponse
s@GetReadinessCheckResponse' {} Maybe Text
a -> GetReadinessCheckResponse
s {$sel:readinessCheckName:GetReadinessCheckResponse' :: Maybe Text
readinessCheckName = Maybe Text
a} :: GetReadinessCheckResponse)

-- | Name of the resource set to be checked.
getReadinessCheckResponse_resourceSet :: Lens.Lens' GetReadinessCheckResponse (Prelude.Maybe Prelude.Text)
getReadinessCheckResponse_resourceSet :: Lens' GetReadinessCheckResponse (Maybe Text)
getReadinessCheckResponse_resourceSet = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetReadinessCheckResponse' {Maybe Text
resourceSet :: Maybe Text
$sel:resourceSet:GetReadinessCheckResponse' :: GetReadinessCheckResponse -> Maybe Text
resourceSet} -> Maybe Text
resourceSet) (\s :: GetReadinessCheckResponse
s@GetReadinessCheckResponse' {} Maybe Text
a -> GetReadinessCheckResponse
s {$sel:resourceSet:GetReadinessCheckResponse' :: Maybe Text
resourceSet = Maybe Text
a} :: GetReadinessCheckResponse)

-- | Undocumented member.
getReadinessCheckResponse_tags :: Lens.Lens' GetReadinessCheckResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
getReadinessCheckResponse_tags :: Lens' GetReadinessCheckResponse (Maybe (HashMap Text Text))
getReadinessCheckResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetReadinessCheckResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:GetReadinessCheckResponse' :: GetReadinessCheckResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: GetReadinessCheckResponse
s@GetReadinessCheckResponse' {} Maybe (HashMap Text Text)
a -> GetReadinessCheckResponse
s {$sel:tags:GetReadinessCheckResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: GetReadinessCheckResponse) 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.
getReadinessCheckResponse_httpStatus :: Lens.Lens' GetReadinessCheckResponse Prelude.Int
getReadinessCheckResponse_httpStatus :: Lens' GetReadinessCheckResponse Int
getReadinessCheckResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetReadinessCheckResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetReadinessCheckResponse' :: GetReadinessCheckResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetReadinessCheckResponse
s@GetReadinessCheckResponse' {} Int
a -> GetReadinessCheckResponse
s {$sel:httpStatus:GetReadinessCheckResponse' :: Int
httpStatus = Int
a} :: GetReadinessCheckResponse)

instance Prelude.NFData GetReadinessCheckResponse where
  rnf :: GetReadinessCheckResponse -> ()
rnf GetReadinessCheckResponse' {Int
Maybe Text
Maybe (HashMap Text Text)
httpStatus :: Int
tags :: Maybe (HashMap Text Text)
resourceSet :: Maybe Text
readinessCheckName :: Maybe Text
readinessCheckArn :: Maybe Text
$sel:httpStatus:GetReadinessCheckResponse' :: GetReadinessCheckResponse -> Int
$sel:tags:GetReadinessCheckResponse' :: GetReadinessCheckResponse -> Maybe (HashMap Text Text)
$sel:resourceSet:GetReadinessCheckResponse' :: GetReadinessCheckResponse -> Maybe Text
$sel:readinessCheckName:GetReadinessCheckResponse' :: GetReadinessCheckResponse -> Maybe Text
$sel:readinessCheckArn:GetReadinessCheckResponse' :: GetReadinessCheckResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
readinessCheckArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
readinessCheckName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
resourceSet
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus