{-# 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.DLM.GetLifecyclePolicy
-- 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 detailed information about the specified lifecycle policy.
module Amazonka.DLM.GetLifecyclePolicy
  ( -- * Creating a Request
    GetLifecyclePolicy (..),
    newGetLifecyclePolicy,

    -- * Request Lenses
    getLifecyclePolicy_policyId,

    -- * Destructuring the Response
    GetLifecyclePolicyResponse (..),
    newGetLifecyclePolicyResponse,

    -- * Response Lenses
    getLifecyclePolicyResponse_policy,
    getLifecyclePolicyResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import Amazonka.DLM.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:/ 'newGetLifecyclePolicy' smart constructor.
data GetLifecyclePolicy = GetLifecyclePolicy'
  { -- | The identifier of the lifecycle policy.
    GetLifecyclePolicy -> Text
policyId :: Prelude.Text
  }
  deriving (GetLifecyclePolicy -> GetLifecyclePolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetLifecyclePolicy -> GetLifecyclePolicy -> Bool
$c/= :: GetLifecyclePolicy -> GetLifecyclePolicy -> Bool
== :: GetLifecyclePolicy -> GetLifecyclePolicy -> Bool
$c== :: GetLifecyclePolicy -> GetLifecyclePolicy -> Bool
Prelude.Eq, ReadPrec [GetLifecyclePolicy]
ReadPrec GetLifecyclePolicy
Int -> ReadS GetLifecyclePolicy
ReadS [GetLifecyclePolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetLifecyclePolicy]
$creadListPrec :: ReadPrec [GetLifecyclePolicy]
readPrec :: ReadPrec GetLifecyclePolicy
$creadPrec :: ReadPrec GetLifecyclePolicy
readList :: ReadS [GetLifecyclePolicy]
$creadList :: ReadS [GetLifecyclePolicy]
readsPrec :: Int -> ReadS GetLifecyclePolicy
$creadsPrec :: Int -> ReadS GetLifecyclePolicy
Prelude.Read, Int -> GetLifecyclePolicy -> ShowS
[GetLifecyclePolicy] -> ShowS
GetLifecyclePolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetLifecyclePolicy] -> ShowS
$cshowList :: [GetLifecyclePolicy] -> ShowS
show :: GetLifecyclePolicy -> String
$cshow :: GetLifecyclePolicy -> String
showsPrec :: Int -> GetLifecyclePolicy -> ShowS
$cshowsPrec :: Int -> GetLifecyclePolicy -> ShowS
Prelude.Show, forall x. Rep GetLifecyclePolicy x -> GetLifecyclePolicy
forall x. GetLifecyclePolicy -> Rep GetLifecyclePolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetLifecyclePolicy x -> GetLifecyclePolicy
$cfrom :: forall x. GetLifecyclePolicy -> Rep GetLifecyclePolicy x
Prelude.Generic)

-- |
-- Create a value of 'GetLifecyclePolicy' 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:
--
-- 'policyId', 'getLifecyclePolicy_policyId' - The identifier of the lifecycle policy.
newGetLifecyclePolicy ::
  -- | 'policyId'
  Prelude.Text ->
  GetLifecyclePolicy
newGetLifecyclePolicy :: Text -> GetLifecyclePolicy
newGetLifecyclePolicy Text
pPolicyId_ =
  GetLifecyclePolicy' {$sel:policyId:GetLifecyclePolicy' :: Text
policyId = Text
pPolicyId_}

-- | The identifier of the lifecycle policy.
getLifecyclePolicy_policyId :: Lens.Lens' GetLifecyclePolicy Prelude.Text
getLifecyclePolicy_policyId :: Lens' GetLifecyclePolicy Text
getLifecyclePolicy_policyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLifecyclePolicy' {Text
policyId :: Text
$sel:policyId:GetLifecyclePolicy' :: GetLifecyclePolicy -> Text
policyId} -> Text
policyId) (\s :: GetLifecyclePolicy
s@GetLifecyclePolicy' {} Text
a -> GetLifecyclePolicy
s {$sel:policyId:GetLifecyclePolicy' :: Text
policyId = Text
a} :: GetLifecyclePolicy)

instance Core.AWSRequest GetLifecyclePolicy where
  type
    AWSResponse GetLifecyclePolicy =
      GetLifecyclePolicyResponse
  request :: (Service -> Service)
-> GetLifecyclePolicy -> Request GetLifecyclePolicy
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 GetLifecyclePolicy
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetLifecyclePolicy)))
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 LifecyclePolicy -> Int -> GetLifecyclePolicyResponse
GetLifecyclePolicyResponse'
            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
"Policy")
            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 GetLifecyclePolicy where
  hashWithSalt :: Int -> GetLifecyclePolicy -> Int
hashWithSalt Int
_salt GetLifecyclePolicy' {Text
policyId :: Text
$sel:policyId:GetLifecyclePolicy' :: GetLifecyclePolicy -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
policyId

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

instance Data.ToHeaders GetLifecyclePolicy where
  toHeaders :: GetLifecyclePolicy -> 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 GetLifecyclePolicy where
  toPath :: GetLifecyclePolicy -> ByteString
toPath GetLifecyclePolicy' {Text
policyId :: Text
$sel:policyId:GetLifecyclePolicy' :: GetLifecyclePolicy -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/policies/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
policyId, ByteString
"/"]

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

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

-- |
-- Create a value of 'GetLifecyclePolicyResponse' 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:
--
-- 'policy', 'getLifecyclePolicyResponse_policy' - Detailed information about the lifecycle policy.
--
-- 'httpStatus', 'getLifecyclePolicyResponse_httpStatus' - The response's http status code.
newGetLifecyclePolicyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetLifecyclePolicyResponse
newGetLifecyclePolicyResponse :: Int -> GetLifecyclePolicyResponse
newGetLifecyclePolicyResponse Int
pHttpStatus_ =
  GetLifecyclePolicyResponse'
    { $sel:policy:GetLifecyclePolicyResponse' :: Maybe LifecyclePolicy
policy =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetLifecyclePolicyResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Detailed information about the lifecycle policy.
getLifecyclePolicyResponse_policy :: Lens.Lens' GetLifecyclePolicyResponse (Prelude.Maybe LifecyclePolicy)
getLifecyclePolicyResponse_policy :: Lens' GetLifecyclePolicyResponse (Maybe LifecyclePolicy)
getLifecyclePolicyResponse_policy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLifecyclePolicyResponse' {Maybe LifecyclePolicy
policy :: Maybe LifecyclePolicy
$sel:policy:GetLifecyclePolicyResponse' :: GetLifecyclePolicyResponse -> Maybe LifecyclePolicy
policy} -> Maybe LifecyclePolicy
policy) (\s :: GetLifecyclePolicyResponse
s@GetLifecyclePolicyResponse' {} Maybe LifecyclePolicy
a -> GetLifecyclePolicyResponse
s {$sel:policy:GetLifecyclePolicyResponse' :: Maybe LifecyclePolicy
policy = Maybe LifecyclePolicy
a} :: GetLifecyclePolicyResponse)

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

instance Prelude.NFData GetLifecyclePolicyResponse where
  rnf :: GetLifecyclePolicyResponse -> ()
rnf GetLifecyclePolicyResponse' {Int
Maybe LifecyclePolicy
httpStatus :: Int
policy :: Maybe LifecyclePolicy
$sel:httpStatus:GetLifecyclePolicyResponse' :: GetLifecyclePolicyResponse -> Int
$sel:policy:GetLifecyclePolicyResponse' :: GetLifecyclePolicyResponse -> Maybe LifecyclePolicy
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe LifecyclePolicy
policy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus