{-# 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.GetKeyGroup
-- 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 key group, including the date and time when the key group was
-- last modified.
--
-- To get a key group, you must provide the key group\'s identifier. If the
-- key group is referenced in a distribution\'s cache behavior, you can get
-- the key group\'s identifier using @ListDistributions@ or
-- @GetDistribution@. If the key group is not referenced in a cache
-- behavior, you can get the identifier using @ListKeyGroups@.
module Amazonka.CloudFront.GetKeyGroup
  ( -- * Creating a Request
    GetKeyGroup (..),
    newGetKeyGroup,

    -- * Request Lenses
    getKeyGroup_id,

    -- * Destructuring the Response
    GetKeyGroupResponse (..),
    newGetKeyGroupResponse,

    -- * Response Lenses
    getKeyGroupResponse_eTag,
    getKeyGroupResponse_keyGroup,
    getKeyGroupResponse_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:/ 'newGetKeyGroup' smart constructor.
data GetKeyGroup = GetKeyGroup'
  { -- | The identifier of the key group that you are getting. To get the
    -- identifier, use @ListKeyGroups@.
    GetKeyGroup -> Text
id :: Prelude.Text
  }
  deriving (GetKeyGroup -> GetKeyGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetKeyGroup -> GetKeyGroup -> Bool
$c/= :: GetKeyGroup -> GetKeyGroup -> Bool
== :: GetKeyGroup -> GetKeyGroup -> Bool
$c== :: GetKeyGroup -> GetKeyGroup -> Bool
Prelude.Eq, ReadPrec [GetKeyGroup]
ReadPrec GetKeyGroup
Int -> ReadS GetKeyGroup
ReadS [GetKeyGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetKeyGroup]
$creadListPrec :: ReadPrec [GetKeyGroup]
readPrec :: ReadPrec GetKeyGroup
$creadPrec :: ReadPrec GetKeyGroup
readList :: ReadS [GetKeyGroup]
$creadList :: ReadS [GetKeyGroup]
readsPrec :: Int -> ReadS GetKeyGroup
$creadsPrec :: Int -> ReadS GetKeyGroup
Prelude.Read, Int -> GetKeyGroup -> ShowS
[GetKeyGroup] -> ShowS
GetKeyGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetKeyGroup] -> ShowS
$cshowList :: [GetKeyGroup] -> ShowS
show :: GetKeyGroup -> String
$cshow :: GetKeyGroup -> String
showsPrec :: Int -> GetKeyGroup -> ShowS
$cshowsPrec :: Int -> GetKeyGroup -> ShowS
Prelude.Show, forall x. Rep GetKeyGroup x -> GetKeyGroup
forall x. GetKeyGroup -> Rep GetKeyGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetKeyGroup x -> GetKeyGroup
$cfrom :: forall x. GetKeyGroup -> Rep GetKeyGroup x
Prelude.Generic)

-- |
-- Create a value of 'GetKeyGroup' 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', 'getKeyGroup_id' - The identifier of the key group that you are getting. To get the
-- identifier, use @ListKeyGroups@.
newGetKeyGroup ::
  -- | 'id'
  Prelude.Text ->
  GetKeyGroup
newGetKeyGroup :: Text -> GetKeyGroup
newGetKeyGroup Text
pId_ = GetKeyGroup' {$sel:id:GetKeyGroup' :: Text
id = Text
pId_}

-- | The identifier of the key group that you are getting. To get the
-- identifier, use @ListKeyGroups@.
getKeyGroup_id :: Lens.Lens' GetKeyGroup Prelude.Text
getKeyGroup_id :: Lens' GetKeyGroup Text
getKeyGroup_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetKeyGroup' {Text
id :: Text
$sel:id:GetKeyGroup' :: GetKeyGroup -> Text
id} -> Text
id) (\s :: GetKeyGroup
s@GetKeyGroup' {} Text
a -> GetKeyGroup
s {$sel:id:GetKeyGroup' :: Text
id = Text
a} :: GetKeyGroup)

instance Core.AWSRequest GetKeyGroup where
  type AWSResponse GetKeyGroup = GetKeyGroupResponse
  request :: (Service -> Service) -> GetKeyGroup -> Request GetKeyGroup
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 GetKeyGroup
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetKeyGroup)))
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 Text -> Maybe KeyGroup -> Int -> GetKeyGroupResponse
GetKeyGroupResponse'
            forall (f :: * -> *) a b. Functor 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 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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

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

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

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

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

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

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

-- |
-- Create a value of 'GetKeyGroupResponse' 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:
--
-- 'eTag', 'getKeyGroupResponse_eTag' - The identifier for this version of the key group.
--
-- 'keyGroup', 'getKeyGroupResponse_keyGroup' - The key group.
--
-- 'httpStatus', 'getKeyGroupResponse_httpStatus' - The response's http status code.
newGetKeyGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetKeyGroupResponse
newGetKeyGroupResponse :: Int -> GetKeyGroupResponse
newGetKeyGroupResponse Int
pHttpStatus_ =
  GetKeyGroupResponse'
    { $sel:eTag:GetKeyGroupResponse' :: Maybe Text
eTag = forall a. Maybe a
Prelude.Nothing,
      $sel:keyGroup:GetKeyGroupResponse' :: Maybe KeyGroup
keyGroup = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetKeyGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The identifier for this version of the key group.
getKeyGroupResponse_eTag :: Lens.Lens' GetKeyGroupResponse (Prelude.Maybe Prelude.Text)
getKeyGroupResponse_eTag :: Lens' GetKeyGroupResponse (Maybe Text)
getKeyGroupResponse_eTag = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetKeyGroupResponse' {Maybe Text
eTag :: Maybe Text
$sel:eTag:GetKeyGroupResponse' :: GetKeyGroupResponse -> Maybe Text
eTag} -> Maybe Text
eTag) (\s :: GetKeyGroupResponse
s@GetKeyGroupResponse' {} Maybe Text
a -> GetKeyGroupResponse
s {$sel:eTag:GetKeyGroupResponse' :: Maybe Text
eTag = Maybe Text
a} :: GetKeyGroupResponse)

-- | The key group.
getKeyGroupResponse_keyGroup :: Lens.Lens' GetKeyGroupResponse (Prelude.Maybe KeyGroup)
getKeyGroupResponse_keyGroup :: Lens' GetKeyGroupResponse (Maybe KeyGroup)
getKeyGroupResponse_keyGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetKeyGroupResponse' {Maybe KeyGroup
keyGroup :: Maybe KeyGroup
$sel:keyGroup:GetKeyGroupResponse' :: GetKeyGroupResponse -> Maybe KeyGroup
keyGroup} -> Maybe KeyGroup
keyGroup) (\s :: GetKeyGroupResponse
s@GetKeyGroupResponse' {} Maybe KeyGroup
a -> GetKeyGroupResponse
s {$sel:keyGroup:GetKeyGroupResponse' :: Maybe KeyGroup
keyGroup = Maybe KeyGroup
a} :: GetKeyGroupResponse)

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

instance Prelude.NFData GetKeyGroupResponse where
  rnf :: GetKeyGroupResponse -> ()
rnf GetKeyGroupResponse' {Int
Maybe Text
Maybe KeyGroup
httpStatus :: Int
keyGroup :: Maybe KeyGroup
eTag :: Maybe Text
$sel:httpStatus:GetKeyGroupResponse' :: GetKeyGroupResponse -> Int
$sel:keyGroup:GetKeyGroupResponse' :: GetKeyGroupResponse -> Maybe KeyGroup
$sel:eTag:GetKeyGroupResponse' :: GetKeyGroupResponse -> Maybe Text
..} =
    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 Maybe KeyGroup
keyGroup
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus