{-# 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.CloudFront.GetCachePolicy
-- 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 a cache policy, including the following metadata:
--
-- -   The policy\'s identifier.
--
-- -   The date and time when the policy was last modified.
--
-- To get a cache policy, you must provide the policy\'s identifier. If the
-- cache policy is attached to a distribution\'s cache behavior, you can
-- get the policy\'s identifier using @ListDistributions@ or
-- @GetDistribution@. If the cache policy is not attached to a cache
-- behavior, you can get the identifier using @ListCachePolicies@.
module Amazonka.CloudFront.GetCachePolicy
  ( -- * Creating a Request
    GetCachePolicy (..),
    newGetCachePolicy,

    -- * Request Lenses
    getCachePolicy_id,

    -- * Destructuring the Response
    GetCachePolicyResponse (..),
    newGetCachePolicyResponse,

    -- * Response Lenses
    getCachePolicyResponse_cachePolicy,
    getCachePolicyResponse_eTag,
    getCachePolicyResponse_httpStatus,
  )
where

import Amazonka.CloudFront.Types
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

-- | /See:/ 'newGetCachePolicy' smart constructor.
data GetCachePolicy = GetCachePolicy'
  { -- | The unique identifier for the cache policy. If the cache policy is
    -- attached to a distribution\'s cache behavior, you can get the policy\'s
    -- identifier using @ListDistributions@ or @GetDistribution@. If the cache
    -- policy is not attached to a cache behavior, you can get the identifier
    -- using @ListCachePolicies@.
    GetCachePolicy -> Text
id :: Prelude.Text
  }
  deriving (GetCachePolicy -> GetCachePolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCachePolicy -> GetCachePolicy -> Bool
$c/= :: GetCachePolicy -> GetCachePolicy -> Bool
== :: GetCachePolicy -> GetCachePolicy -> Bool
$c== :: GetCachePolicy -> GetCachePolicy -> Bool
Prelude.Eq, ReadPrec [GetCachePolicy]
ReadPrec GetCachePolicy
Int -> ReadS GetCachePolicy
ReadS [GetCachePolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCachePolicy]
$creadListPrec :: ReadPrec [GetCachePolicy]
readPrec :: ReadPrec GetCachePolicy
$creadPrec :: ReadPrec GetCachePolicy
readList :: ReadS [GetCachePolicy]
$creadList :: ReadS [GetCachePolicy]
readsPrec :: Int -> ReadS GetCachePolicy
$creadsPrec :: Int -> ReadS GetCachePolicy
Prelude.Read, Int -> GetCachePolicy -> ShowS
[GetCachePolicy] -> ShowS
GetCachePolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCachePolicy] -> ShowS
$cshowList :: [GetCachePolicy] -> ShowS
show :: GetCachePolicy -> String
$cshow :: GetCachePolicy -> String
showsPrec :: Int -> GetCachePolicy -> ShowS
$cshowsPrec :: Int -> GetCachePolicy -> ShowS
Prelude.Show, forall x. Rep GetCachePolicy x -> GetCachePolicy
forall x. GetCachePolicy -> Rep GetCachePolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetCachePolicy x -> GetCachePolicy
$cfrom :: forall x. GetCachePolicy -> Rep GetCachePolicy x
Prelude.Generic)

-- |
-- Create a value of 'GetCachePolicy' 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:
--
-- 'id', 'getCachePolicy_id' - The unique identifier for the cache policy. If the cache policy is
-- attached to a distribution\'s cache behavior, you can get the policy\'s
-- identifier using @ListDistributions@ or @GetDistribution@. If the cache
-- policy is not attached to a cache behavior, you can get the identifier
-- using @ListCachePolicies@.
newGetCachePolicy ::
  -- | 'id'
  Prelude.Text ->
  GetCachePolicy
newGetCachePolicy :: Text -> GetCachePolicy
newGetCachePolicy Text
pId_ = GetCachePolicy' {$sel:id:GetCachePolicy' :: Text
id = Text
pId_}

-- | The unique identifier for the cache policy. If the cache policy is
-- attached to a distribution\'s cache behavior, you can get the policy\'s
-- identifier using @ListDistributions@ or @GetDistribution@. If the cache
-- policy is not attached to a cache behavior, you can get the identifier
-- using @ListCachePolicies@.
getCachePolicy_id :: Lens.Lens' GetCachePolicy Prelude.Text
getCachePolicy_id :: Lens' GetCachePolicy Text
getCachePolicy_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCachePolicy' {Text
id :: Text
$sel:id:GetCachePolicy' :: GetCachePolicy -> Text
id} -> Text
id) (\s :: GetCachePolicy
s@GetCachePolicy' {} Text
a -> GetCachePolicy
s {$sel:id:GetCachePolicy' :: Text
id = Text
a} :: GetCachePolicy)

instance Core.AWSRequest GetCachePolicy where
  type
    AWSResponse GetCachePolicy =
      GetCachePolicyResponse
  request :: (Service -> Service) -> GetCachePolicy -> Request GetCachePolicy
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 GetCachePolicy
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetCachePolicy)))
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 ->
          Maybe CachePolicy -> Maybe Text -> Int -> GetCachePolicyResponse
GetCachePolicyResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (forall a. FromXML a => [Node] -> Either String a
Data.parseXML [Node]
x)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"ETag")
            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 GetCachePolicy where
  hashWithSalt :: Int -> GetCachePolicy -> Int
hashWithSalt Int
_salt GetCachePolicy' {Text
id :: Text
$sel:id:GetCachePolicy' :: GetCachePolicy -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id

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

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

instance Data.ToPath GetCachePolicy where
  toPath :: GetCachePolicy -> ByteString
toPath GetCachePolicy' {Text
id :: Text
$sel:id:GetCachePolicy' :: GetCachePolicy -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/2020-05-31/cache-policy/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
id]

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

-- | /See:/ 'newGetCachePolicyResponse' smart constructor.
data GetCachePolicyResponse = GetCachePolicyResponse'
  { -- | The cache policy.
    GetCachePolicyResponse -> Maybe CachePolicy
cachePolicy :: Prelude.Maybe CachePolicy,
    -- | The current version of the cache policy.
    GetCachePolicyResponse -> Maybe Text
eTag :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetCachePolicyResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetCachePolicyResponse -> GetCachePolicyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCachePolicyResponse -> GetCachePolicyResponse -> Bool
$c/= :: GetCachePolicyResponse -> GetCachePolicyResponse -> Bool
== :: GetCachePolicyResponse -> GetCachePolicyResponse -> Bool
$c== :: GetCachePolicyResponse -> GetCachePolicyResponse -> Bool
Prelude.Eq, ReadPrec [GetCachePolicyResponse]
ReadPrec GetCachePolicyResponse
Int -> ReadS GetCachePolicyResponse
ReadS [GetCachePolicyResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCachePolicyResponse]
$creadListPrec :: ReadPrec [GetCachePolicyResponse]
readPrec :: ReadPrec GetCachePolicyResponse
$creadPrec :: ReadPrec GetCachePolicyResponse
readList :: ReadS [GetCachePolicyResponse]
$creadList :: ReadS [GetCachePolicyResponse]
readsPrec :: Int -> ReadS GetCachePolicyResponse
$creadsPrec :: Int -> ReadS GetCachePolicyResponse
Prelude.Read, Int -> GetCachePolicyResponse -> ShowS
[GetCachePolicyResponse] -> ShowS
GetCachePolicyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCachePolicyResponse] -> ShowS
$cshowList :: [GetCachePolicyResponse] -> ShowS
show :: GetCachePolicyResponse -> String
$cshow :: GetCachePolicyResponse -> String
showsPrec :: Int -> GetCachePolicyResponse -> ShowS
$cshowsPrec :: Int -> GetCachePolicyResponse -> ShowS
Prelude.Show, forall x. Rep GetCachePolicyResponse x -> GetCachePolicyResponse
forall x. GetCachePolicyResponse -> Rep GetCachePolicyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetCachePolicyResponse x -> GetCachePolicyResponse
$cfrom :: forall x. GetCachePolicyResponse -> Rep GetCachePolicyResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetCachePolicyResponse' 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:
--
-- 'cachePolicy', 'getCachePolicyResponse_cachePolicy' - The cache policy.
--
-- 'eTag', 'getCachePolicyResponse_eTag' - The current version of the cache policy.
--
-- 'httpStatus', 'getCachePolicyResponse_httpStatus' - The response's http status code.
newGetCachePolicyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetCachePolicyResponse
newGetCachePolicyResponse :: Int -> GetCachePolicyResponse
newGetCachePolicyResponse Int
pHttpStatus_ =
  GetCachePolicyResponse'
    { $sel:cachePolicy:GetCachePolicyResponse' :: Maybe CachePolicy
cachePolicy =
        forall a. Maybe a
Prelude.Nothing,
      $sel:eTag:GetCachePolicyResponse' :: Maybe Text
eTag = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetCachePolicyResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The cache policy.
getCachePolicyResponse_cachePolicy :: Lens.Lens' GetCachePolicyResponse (Prelude.Maybe CachePolicy)
getCachePolicyResponse_cachePolicy :: Lens' GetCachePolicyResponse (Maybe CachePolicy)
getCachePolicyResponse_cachePolicy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCachePolicyResponse' {Maybe CachePolicy
cachePolicy :: Maybe CachePolicy
$sel:cachePolicy:GetCachePolicyResponse' :: GetCachePolicyResponse -> Maybe CachePolicy
cachePolicy} -> Maybe CachePolicy
cachePolicy) (\s :: GetCachePolicyResponse
s@GetCachePolicyResponse' {} Maybe CachePolicy
a -> GetCachePolicyResponse
s {$sel:cachePolicy:GetCachePolicyResponse' :: Maybe CachePolicy
cachePolicy = Maybe CachePolicy
a} :: GetCachePolicyResponse)

-- | The current version of the cache policy.
getCachePolicyResponse_eTag :: Lens.Lens' GetCachePolicyResponse (Prelude.Maybe Prelude.Text)
getCachePolicyResponse_eTag :: Lens' GetCachePolicyResponse (Maybe Text)
getCachePolicyResponse_eTag = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCachePolicyResponse' {Maybe Text
eTag :: Maybe Text
$sel:eTag:GetCachePolicyResponse' :: GetCachePolicyResponse -> Maybe Text
eTag} -> Maybe Text
eTag) (\s :: GetCachePolicyResponse
s@GetCachePolicyResponse' {} Maybe Text
a -> GetCachePolicyResponse
s {$sel:eTag:GetCachePolicyResponse' :: Maybe Text
eTag = Maybe Text
a} :: GetCachePolicyResponse)

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

instance Prelude.NFData GetCachePolicyResponse where
  rnf :: GetCachePolicyResponse -> ()
rnf GetCachePolicyResponse' {Int
Maybe Text
Maybe CachePolicy
httpStatus :: Int
eTag :: Maybe Text
cachePolicy :: Maybe CachePolicy
$sel:httpStatus:GetCachePolicyResponse' :: GetCachePolicyResponse -> Int
$sel:eTag:GetCachePolicyResponse' :: GetCachePolicyResponse -> Maybe Text
$sel:cachePolicy:GetCachePolicyResponse' :: GetCachePolicyResponse -> Maybe CachePolicy
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe CachePolicy
cachePolicy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
eTag
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus