{-# 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.ElasticBeanstalk.DescribePlatformVersion
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describes a platform version. Provides full details. Compare to
-- ListPlatformVersions, which provides summary information about a list of
-- platform versions.
--
-- For definitions of platform version and other platform-related terms,
-- see
-- <https://docs.aws.amazon.com/elasticbeanstalk/latest/dg/platforms-glossary.html AWS Elastic Beanstalk Platforms Glossary>.
module Amazonka.ElasticBeanstalk.DescribePlatformVersion
  ( -- * Creating a Request
    DescribePlatformVersion (..),
    newDescribePlatformVersion,

    -- * Request Lenses
    describePlatformVersion_platformArn,

    -- * Destructuring the Response
    DescribePlatformVersionResponse (..),
    newDescribePlatformVersionResponse,

    -- * Response Lenses
    describePlatformVersionResponse_platformDescription,
    describePlatformVersionResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.ElasticBeanstalk.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDescribePlatformVersion' smart constructor.
data DescribePlatformVersion = DescribePlatformVersion'
  { -- | The ARN of the platform version.
    DescribePlatformVersion -> Maybe Text
platformArn :: Prelude.Maybe Prelude.Text
  }
  deriving (DescribePlatformVersion -> DescribePlatformVersion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribePlatformVersion -> DescribePlatformVersion -> Bool
$c/= :: DescribePlatformVersion -> DescribePlatformVersion -> Bool
== :: DescribePlatformVersion -> DescribePlatformVersion -> Bool
$c== :: DescribePlatformVersion -> DescribePlatformVersion -> Bool
Prelude.Eq, ReadPrec [DescribePlatformVersion]
ReadPrec DescribePlatformVersion
Int -> ReadS DescribePlatformVersion
ReadS [DescribePlatformVersion]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribePlatformVersion]
$creadListPrec :: ReadPrec [DescribePlatformVersion]
readPrec :: ReadPrec DescribePlatformVersion
$creadPrec :: ReadPrec DescribePlatformVersion
readList :: ReadS [DescribePlatformVersion]
$creadList :: ReadS [DescribePlatformVersion]
readsPrec :: Int -> ReadS DescribePlatformVersion
$creadsPrec :: Int -> ReadS DescribePlatformVersion
Prelude.Read, Int -> DescribePlatformVersion -> ShowS
[DescribePlatformVersion] -> ShowS
DescribePlatformVersion -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribePlatformVersion] -> ShowS
$cshowList :: [DescribePlatformVersion] -> ShowS
show :: DescribePlatformVersion -> String
$cshow :: DescribePlatformVersion -> String
showsPrec :: Int -> DescribePlatformVersion -> ShowS
$cshowsPrec :: Int -> DescribePlatformVersion -> ShowS
Prelude.Show, forall x. Rep DescribePlatformVersion x -> DescribePlatformVersion
forall x. DescribePlatformVersion -> Rep DescribePlatformVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribePlatformVersion x -> DescribePlatformVersion
$cfrom :: forall x. DescribePlatformVersion -> Rep DescribePlatformVersion x
Prelude.Generic)

-- |
-- Create a value of 'DescribePlatformVersion' 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:
--
-- 'platformArn', 'describePlatformVersion_platformArn' - The ARN of the platform version.
newDescribePlatformVersion ::
  DescribePlatformVersion
newDescribePlatformVersion :: DescribePlatformVersion
newDescribePlatformVersion =
  DescribePlatformVersion'
    { $sel:platformArn:DescribePlatformVersion' :: Maybe Text
platformArn =
        forall a. Maybe a
Prelude.Nothing
    }

-- | The ARN of the platform version.
describePlatformVersion_platformArn :: Lens.Lens' DescribePlatformVersion (Prelude.Maybe Prelude.Text)
describePlatformVersion_platformArn :: Lens' DescribePlatformVersion (Maybe Text)
describePlatformVersion_platformArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribePlatformVersion' {Maybe Text
platformArn :: Maybe Text
$sel:platformArn:DescribePlatformVersion' :: DescribePlatformVersion -> Maybe Text
platformArn} -> Maybe Text
platformArn) (\s :: DescribePlatformVersion
s@DescribePlatformVersion' {} Maybe Text
a -> DescribePlatformVersion
s {$sel:platformArn:DescribePlatformVersion' :: Maybe Text
platformArn = Maybe Text
a} :: DescribePlatformVersion)

instance Core.AWSRequest DescribePlatformVersion where
  type
    AWSResponse DescribePlatformVersion =
      DescribePlatformVersionResponse
  request :: (Service -> Service)
-> DescribePlatformVersion -> Request DescribePlatformVersion
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribePlatformVersion
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribePlatformVersion)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"DescribePlatformVersionResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe PlatformDescription -> Int -> DescribePlatformVersionResponse
DescribePlatformVersionResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PlatformDescription")
            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 DescribePlatformVersion where
  hashWithSalt :: Int -> DescribePlatformVersion -> Int
hashWithSalt Int
_salt DescribePlatformVersion' {Maybe Text
platformArn :: Maybe Text
$sel:platformArn:DescribePlatformVersion' :: DescribePlatformVersion -> Maybe Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
platformArn

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

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

instance Data.ToPath DescribePlatformVersion where
  toPath :: DescribePlatformVersion -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery DescribePlatformVersion where
  toQuery :: DescribePlatformVersion -> QueryString
toQuery DescribePlatformVersion' {Maybe Text
platformArn :: Maybe Text
$sel:platformArn:DescribePlatformVersion' :: DescribePlatformVersion -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DescribePlatformVersion" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-12-01" :: Prelude.ByteString),
        ByteString
"PlatformArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
platformArn
      ]

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

-- |
-- Create a value of 'DescribePlatformVersionResponse' 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:
--
-- 'platformDescription', 'describePlatformVersionResponse_platformDescription' - Detailed information about the platform version.
--
-- 'httpStatus', 'describePlatformVersionResponse_httpStatus' - The response's http status code.
newDescribePlatformVersionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribePlatformVersionResponse
newDescribePlatformVersionResponse :: Int -> DescribePlatformVersionResponse
newDescribePlatformVersionResponse Int
pHttpStatus_ =
  DescribePlatformVersionResponse'
    { $sel:platformDescription:DescribePlatformVersionResponse' :: Maybe PlatformDescription
platformDescription =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribePlatformVersionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Detailed information about the platform version.
describePlatformVersionResponse_platformDescription :: Lens.Lens' DescribePlatformVersionResponse (Prelude.Maybe PlatformDescription)
describePlatformVersionResponse_platformDescription :: Lens' DescribePlatformVersionResponse (Maybe PlatformDescription)
describePlatformVersionResponse_platformDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribePlatformVersionResponse' {Maybe PlatformDescription
platformDescription :: Maybe PlatformDescription
$sel:platformDescription:DescribePlatformVersionResponse' :: DescribePlatformVersionResponse -> Maybe PlatformDescription
platformDescription} -> Maybe PlatformDescription
platformDescription) (\s :: DescribePlatformVersionResponse
s@DescribePlatformVersionResponse' {} Maybe PlatformDescription
a -> DescribePlatformVersionResponse
s {$sel:platformDescription:DescribePlatformVersionResponse' :: Maybe PlatformDescription
platformDescription = Maybe PlatformDescription
a} :: DescribePlatformVersionResponse)

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

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