{-# 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.AppConfig.GetHostedConfigurationVersion
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves information about a specific configuration version.
module Amazonka.AppConfig.GetHostedConfigurationVersion
  ( -- * Creating a Request
    GetHostedConfigurationVersion (..),
    newGetHostedConfigurationVersion,

    -- * Request Lenses
    getHostedConfigurationVersion_applicationId,
    getHostedConfigurationVersion_configurationProfileId,
    getHostedConfigurationVersion_versionNumber,

    -- * Destructuring the Response
    HostedConfigurationVersion (..),
    newHostedConfigurationVersion,

    -- * Response Lenses
    hostedConfigurationVersion_applicationId,
    hostedConfigurationVersion_configurationProfileId,
    hostedConfigurationVersion_content,
    hostedConfigurationVersion_contentType,
    hostedConfigurationVersion_description,
    hostedConfigurationVersion_versionNumber,
  )
where

import Amazonka.AppConfig.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:/ 'newGetHostedConfigurationVersion' smart constructor.
data GetHostedConfigurationVersion = GetHostedConfigurationVersion'
  { -- | The application ID.
    GetHostedConfigurationVersion -> Text
applicationId :: Prelude.Text,
    -- | The configuration profile ID.
    GetHostedConfigurationVersion -> Text
configurationProfileId :: Prelude.Text,
    -- | The version.
    GetHostedConfigurationVersion -> Int
versionNumber :: Prelude.Int
  }
  deriving (GetHostedConfigurationVersion
-> GetHostedConfigurationVersion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetHostedConfigurationVersion
-> GetHostedConfigurationVersion -> Bool
$c/= :: GetHostedConfigurationVersion
-> GetHostedConfigurationVersion -> Bool
== :: GetHostedConfigurationVersion
-> GetHostedConfigurationVersion -> Bool
$c== :: GetHostedConfigurationVersion
-> GetHostedConfigurationVersion -> Bool
Prelude.Eq, ReadPrec [GetHostedConfigurationVersion]
ReadPrec GetHostedConfigurationVersion
Int -> ReadS GetHostedConfigurationVersion
ReadS [GetHostedConfigurationVersion]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetHostedConfigurationVersion]
$creadListPrec :: ReadPrec [GetHostedConfigurationVersion]
readPrec :: ReadPrec GetHostedConfigurationVersion
$creadPrec :: ReadPrec GetHostedConfigurationVersion
readList :: ReadS [GetHostedConfigurationVersion]
$creadList :: ReadS [GetHostedConfigurationVersion]
readsPrec :: Int -> ReadS GetHostedConfigurationVersion
$creadsPrec :: Int -> ReadS GetHostedConfigurationVersion
Prelude.Read, Int -> GetHostedConfigurationVersion -> ShowS
[GetHostedConfigurationVersion] -> ShowS
GetHostedConfigurationVersion -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetHostedConfigurationVersion] -> ShowS
$cshowList :: [GetHostedConfigurationVersion] -> ShowS
show :: GetHostedConfigurationVersion -> String
$cshow :: GetHostedConfigurationVersion -> String
showsPrec :: Int -> GetHostedConfigurationVersion -> ShowS
$cshowsPrec :: Int -> GetHostedConfigurationVersion -> ShowS
Prelude.Show, forall x.
Rep GetHostedConfigurationVersion x
-> GetHostedConfigurationVersion
forall x.
GetHostedConfigurationVersion
-> Rep GetHostedConfigurationVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetHostedConfigurationVersion x
-> GetHostedConfigurationVersion
$cfrom :: forall x.
GetHostedConfigurationVersion
-> Rep GetHostedConfigurationVersion x
Prelude.Generic)

-- |
-- Create a value of 'GetHostedConfigurationVersion' 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:
--
-- 'applicationId', 'getHostedConfigurationVersion_applicationId' - The application ID.
--
-- 'configurationProfileId', 'getHostedConfigurationVersion_configurationProfileId' - The configuration profile ID.
--
-- 'versionNumber', 'getHostedConfigurationVersion_versionNumber' - The version.
newGetHostedConfigurationVersion ::
  -- | 'applicationId'
  Prelude.Text ->
  -- | 'configurationProfileId'
  Prelude.Text ->
  -- | 'versionNumber'
  Prelude.Int ->
  GetHostedConfigurationVersion
newGetHostedConfigurationVersion :: Text -> Text -> Int -> GetHostedConfigurationVersion
newGetHostedConfigurationVersion
  Text
pApplicationId_
  Text
pConfigurationProfileId_
  Int
pVersionNumber_ =
    GetHostedConfigurationVersion'
      { $sel:applicationId:GetHostedConfigurationVersion' :: Text
applicationId =
          Text
pApplicationId_,
        $sel:configurationProfileId:GetHostedConfigurationVersion' :: Text
configurationProfileId =
          Text
pConfigurationProfileId_,
        $sel:versionNumber:GetHostedConfigurationVersion' :: Int
versionNumber = Int
pVersionNumber_
      }

-- | The application ID.
getHostedConfigurationVersion_applicationId :: Lens.Lens' GetHostedConfigurationVersion Prelude.Text
getHostedConfigurationVersion_applicationId :: Lens' GetHostedConfigurationVersion Text
getHostedConfigurationVersion_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetHostedConfigurationVersion' {Text
applicationId :: Text
$sel:applicationId:GetHostedConfigurationVersion' :: GetHostedConfigurationVersion -> Text
applicationId} -> Text
applicationId) (\s :: GetHostedConfigurationVersion
s@GetHostedConfigurationVersion' {} Text
a -> GetHostedConfigurationVersion
s {$sel:applicationId:GetHostedConfigurationVersion' :: Text
applicationId = Text
a} :: GetHostedConfigurationVersion)

-- | The configuration profile ID.
getHostedConfigurationVersion_configurationProfileId :: Lens.Lens' GetHostedConfigurationVersion Prelude.Text
getHostedConfigurationVersion_configurationProfileId :: Lens' GetHostedConfigurationVersion Text
getHostedConfigurationVersion_configurationProfileId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetHostedConfigurationVersion' {Text
configurationProfileId :: Text
$sel:configurationProfileId:GetHostedConfigurationVersion' :: GetHostedConfigurationVersion -> Text
configurationProfileId} -> Text
configurationProfileId) (\s :: GetHostedConfigurationVersion
s@GetHostedConfigurationVersion' {} Text
a -> GetHostedConfigurationVersion
s {$sel:configurationProfileId:GetHostedConfigurationVersion' :: Text
configurationProfileId = Text
a} :: GetHostedConfigurationVersion)

-- | The version.
getHostedConfigurationVersion_versionNumber :: Lens.Lens' GetHostedConfigurationVersion Prelude.Int
getHostedConfigurationVersion_versionNumber :: Lens' GetHostedConfigurationVersion Int
getHostedConfigurationVersion_versionNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetHostedConfigurationVersion' {Int
versionNumber :: Int
$sel:versionNumber:GetHostedConfigurationVersion' :: GetHostedConfigurationVersion -> Int
versionNumber} -> Int
versionNumber) (\s :: GetHostedConfigurationVersion
s@GetHostedConfigurationVersion' {} Int
a -> GetHostedConfigurationVersion
s {$sel:versionNumber:GetHostedConfigurationVersion' :: Int
versionNumber = Int
a} :: GetHostedConfigurationVersion)

instance
  Core.AWSRequest
    GetHostedConfigurationVersion
  where
  type
    AWSResponse GetHostedConfigurationVersion =
      HostedConfigurationVersion
  request :: (Service -> Service)
-> GetHostedConfigurationVersion
-> Request GetHostedConfigurationVersion
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 GetHostedConfigurationVersion
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetHostedConfigurationVersion)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int
 -> ResponseHeaders -> ByteString -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveBytes
      ( \Int
s ResponseHeaders
h ByteString
x ->
          Maybe Text
-> Maybe Text
-> Maybe (Sensitive ByteString)
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> HostedConfigurationVersion
HostedConfigurationVersion'
            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
"Application-Id")
            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
"Configuration-Profile-Id")
            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. a -> Maybe a
Prelude.Just (coerce :: forall a b. Coercible a b => a -> b
Prelude.coerce ByteString
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
"Content-Type")
            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
"Description")
            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
"Version-Number")
      )

instance
  Prelude.Hashable
    GetHostedConfigurationVersion
  where
  hashWithSalt :: Int -> GetHostedConfigurationVersion -> Int
hashWithSalt Int
_salt GetHostedConfigurationVersion' {Int
Text
versionNumber :: Int
configurationProfileId :: Text
applicationId :: Text
$sel:versionNumber:GetHostedConfigurationVersion' :: GetHostedConfigurationVersion -> Int
$sel:configurationProfileId:GetHostedConfigurationVersion' :: GetHostedConfigurationVersion -> Text
$sel:applicationId:GetHostedConfigurationVersion' :: GetHostedConfigurationVersion -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
configurationProfileId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Int
versionNumber

instance Prelude.NFData GetHostedConfigurationVersion where
  rnf :: GetHostedConfigurationVersion -> ()
rnf GetHostedConfigurationVersion' {Int
Text
versionNumber :: Int
configurationProfileId :: Text
applicationId :: Text
$sel:versionNumber:GetHostedConfigurationVersion' :: GetHostedConfigurationVersion -> Int
$sel:configurationProfileId:GetHostedConfigurationVersion' :: GetHostedConfigurationVersion -> Text
$sel:applicationId:GetHostedConfigurationVersion' :: GetHostedConfigurationVersion -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
applicationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
configurationProfileId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
versionNumber

instance Data.ToHeaders GetHostedConfigurationVersion where
  toHeaders :: GetHostedConfigurationVersion -> 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 GetHostedConfigurationVersion where
  toPath :: GetHostedConfigurationVersion -> ByteString
toPath GetHostedConfigurationVersion' {Int
Text
versionNumber :: Int
configurationProfileId :: Text
applicationId :: Text
$sel:versionNumber:GetHostedConfigurationVersion' :: GetHostedConfigurationVersion -> Int
$sel:configurationProfileId:GetHostedConfigurationVersion' :: GetHostedConfigurationVersion -> Text
$sel:applicationId:GetHostedConfigurationVersion' :: GetHostedConfigurationVersion -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/applications/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationId,
        ByteString
"/configurationprofiles/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
configurationProfileId,
        ByteString
"/hostedconfigurationversions/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Int
versionNumber
      ]

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