{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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.Types.PlatformDescription
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.ElasticBeanstalk.Types.PlatformDescription 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.CustomAmi
import Amazonka.ElasticBeanstalk.Types.PlatformFramework
import Amazonka.ElasticBeanstalk.Types.PlatformProgrammingLanguage
import Amazonka.ElasticBeanstalk.Types.PlatformStatus
import qualified Amazonka.Prelude as Prelude

-- | Detailed information about a platform version.
--
-- /See:/ 'newPlatformDescription' smart constructor.
data PlatformDescription = PlatformDescription'
  { -- | The custom AMIs supported by the platform version.
    PlatformDescription -> Maybe [CustomAmi]
customAmiList :: Prelude.Maybe [CustomAmi],
    -- | The date when the platform version was created.
    PlatformDescription -> Maybe ISO8601
dateCreated :: Prelude.Maybe Data.ISO8601,
    -- | The date when the platform version was last updated.
    PlatformDescription -> Maybe ISO8601
dateUpdated :: Prelude.Maybe Data.ISO8601,
    -- | The description of the platform version.
    PlatformDescription -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The frameworks supported by the platform version.
    PlatformDescription -> Maybe [PlatformFramework]
frameworks :: Prelude.Maybe [PlatformFramework],
    -- | Information about the maintainer of the platform version.
    PlatformDescription -> Maybe Text
maintainer :: Prelude.Maybe Prelude.Text,
    -- | The operating system used by the platform version.
    PlatformDescription -> Maybe Text
operatingSystemName :: Prelude.Maybe Prelude.Text,
    -- | The version of the operating system used by the platform version.
    PlatformDescription -> Maybe Text
operatingSystemVersion :: Prelude.Maybe Prelude.Text,
    -- | The ARN of the platform version.
    PlatformDescription -> Maybe Text
platformArn :: Prelude.Maybe Prelude.Text,
    -- | The state of the platform version\'s branch in its lifecycle.
    --
    -- Possible values: @Beta@ | @Supported@ | @Deprecated@ | @Retired@
    PlatformDescription -> Maybe Text
platformBranchLifecycleState :: Prelude.Maybe Prelude.Text,
    -- | The platform branch to which the platform version belongs.
    PlatformDescription -> Maybe Text
platformBranchName :: Prelude.Maybe Prelude.Text,
    -- | The category of the platform version.
    PlatformDescription -> Maybe Text
platformCategory :: Prelude.Maybe Prelude.Text,
    -- | The state of the platform version in its lifecycle.
    --
    -- Possible values: @Recommended@ | @null@
    --
    -- If a null value is returned, the platform version isn\'t the recommended
    -- one for its branch. Each platform branch has a single recommended
    -- platform version, typically the most recent one.
    PlatformDescription -> Maybe Text
platformLifecycleState :: Prelude.Maybe Prelude.Text,
    -- | The name of the platform version.
    PlatformDescription -> Maybe Text
platformName :: Prelude.Maybe Prelude.Text,
    -- | The AWS account ID of the person who created the platform version.
    PlatformDescription -> Maybe Text
platformOwner :: Prelude.Maybe Prelude.Text,
    -- | The status of the platform version.
    PlatformDescription -> Maybe PlatformStatus
platformStatus :: Prelude.Maybe PlatformStatus,
    -- | The version of the platform version.
    PlatformDescription -> Maybe Text
platformVersion :: Prelude.Maybe Prelude.Text,
    -- | The programming languages supported by the platform version.
    PlatformDescription -> Maybe [PlatformProgrammingLanguage]
programmingLanguages :: Prelude.Maybe [PlatformProgrammingLanguage],
    -- | The name of the solution stack used by the platform version.
    PlatformDescription -> Maybe Text
solutionStackName :: Prelude.Maybe Prelude.Text,
    -- | The additions supported by the platform version.
    PlatformDescription -> Maybe [Text]
supportedAddonList :: Prelude.Maybe [Prelude.Text],
    -- | The tiers supported by the platform version.
    PlatformDescription -> Maybe [Text]
supportedTierList :: Prelude.Maybe [Prelude.Text]
  }
  deriving (PlatformDescription -> PlatformDescription -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PlatformDescription -> PlatformDescription -> Bool
$c/= :: PlatformDescription -> PlatformDescription -> Bool
== :: PlatformDescription -> PlatformDescription -> Bool
$c== :: PlatformDescription -> PlatformDescription -> Bool
Prelude.Eq, ReadPrec [PlatformDescription]
ReadPrec PlatformDescription
Int -> ReadS PlatformDescription
ReadS [PlatformDescription]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PlatformDescription]
$creadListPrec :: ReadPrec [PlatformDescription]
readPrec :: ReadPrec PlatformDescription
$creadPrec :: ReadPrec PlatformDescription
readList :: ReadS [PlatformDescription]
$creadList :: ReadS [PlatformDescription]
readsPrec :: Int -> ReadS PlatformDescription
$creadsPrec :: Int -> ReadS PlatformDescription
Prelude.Read, Int -> PlatformDescription -> ShowS
[PlatformDescription] -> ShowS
PlatformDescription -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PlatformDescription] -> ShowS
$cshowList :: [PlatformDescription] -> ShowS
show :: PlatformDescription -> String
$cshow :: PlatformDescription -> String
showsPrec :: Int -> PlatformDescription -> ShowS
$cshowsPrec :: Int -> PlatformDescription -> ShowS
Prelude.Show, forall x. Rep PlatformDescription x -> PlatformDescription
forall x. PlatformDescription -> Rep PlatformDescription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PlatformDescription x -> PlatformDescription
$cfrom :: forall x. PlatformDescription -> Rep PlatformDescription x
Prelude.Generic)

-- |
-- Create a value of 'PlatformDescription' 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:
--
-- 'customAmiList', 'platformDescription_customAmiList' - The custom AMIs supported by the platform version.
--
-- 'dateCreated', 'platformDescription_dateCreated' - The date when the platform version was created.
--
-- 'dateUpdated', 'platformDescription_dateUpdated' - The date when the platform version was last updated.
--
-- 'description', 'platformDescription_description' - The description of the platform version.
--
-- 'frameworks', 'platformDescription_frameworks' - The frameworks supported by the platform version.
--
-- 'maintainer', 'platformDescription_maintainer' - Information about the maintainer of the platform version.
--
-- 'operatingSystemName', 'platformDescription_operatingSystemName' - The operating system used by the platform version.
--
-- 'operatingSystemVersion', 'platformDescription_operatingSystemVersion' - The version of the operating system used by the platform version.
--
-- 'platformArn', 'platformDescription_platformArn' - The ARN of the platform version.
--
-- 'platformBranchLifecycleState', 'platformDescription_platformBranchLifecycleState' - The state of the platform version\'s branch in its lifecycle.
--
-- Possible values: @Beta@ | @Supported@ | @Deprecated@ | @Retired@
--
-- 'platformBranchName', 'platformDescription_platformBranchName' - The platform branch to which the platform version belongs.
--
-- 'platformCategory', 'platformDescription_platformCategory' - The category of the platform version.
--
-- 'platformLifecycleState', 'platformDescription_platformLifecycleState' - The state of the platform version in its lifecycle.
--
-- Possible values: @Recommended@ | @null@
--
-- If a null value is returned, the platform version isn\'t the recommended
-- one for its branch. Each platform branch has a single recommended
-- platform version, typically the most recent one.
--
-- 'platformName', 'platformDescription_platformName' - The name of the platform version.
--
-- 'platformOwner', 'platformDescription_platformOwner' - The AWS account ID of the person who created the platform version.
--
-- 'platformStatus', 'platformDescription_platformStatus' - The status of the platform version.
--
-- 'platformVersion', 'platformDescription_platformVersion' - The version of the platform version.
--
-- 'programmingLanguages', 'platformDescription_programmingLanguages' - The programming languages supported by the platform version.
--
-- 'solutionStackName', 'platformDescription_solutionStackName' - The name of the solution stack used by the platform version.
--
-- 'supportedAddonList', 'platformDescription_supportedAddonList' - The additions supported by the platform version.
--
-- 'supportedTierList', 'platformDescription_supportedTierList' - The tiers supported by the platform version.
newPlatformDescription ::
  PlatformDescription
newPlatformDescription :: PlatformDescription
newPlatformDescription =
  PlatformDescription'
    { $sel:customAmiList:PlatformDescription' :: Maybe [CustomAmi]
customAmiList =
        forall a. Maybe a
Prelude.Nothing,
      $sel:dateCreated:PlatformDescription' :: Maybe ISO8601
dateCreated = forall a. Maybe a
Prelude.Nothing,
      $sel:dateUpdated:PlatformDescription' :: Maybe ISO8601
dateUpdated = forall a. Maybe a
Prelude.Nothing,
      $sel:description:PlatformDescription' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:frameworks:PlatformDescription' :: Maybe [PlatformFramework]
frameworks = forall a. Maybe a
Prelude.Nothing,
      $sel:maintainer:PlatformDescription' :: Maybe Text
maintainer = forall a. Maybe a
Prelude.Nothing,
      $sel:operatingSystemName:PlatformDescription' :: Maybe Text
operatingSystemName = forall a. Maybe a
Prelude.Nothing,
      $sel:operatingSystemVersion:PlatformDescription' :: Maybe Text
operatingSystemVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:platformArn:PlatformDescription' :: Maybe Text
platformArn = forall a. Maybe a
Prelude.Nothing,
      $sel:platformBranchLifecycleState:PlatformDescription' :: Maybe Text
platformBranchLifecycleState = forall a. Maybe a
Prelude.Nothing,
      $sel:platformBranchName:PlatformDescription' :: Maybe Text
platformBranchName = forall a. Maybe a
Prelude.Nothing,
      $sel:platformCategory:PlatformDescription' :: Maybe Text
platformCategory = forall a. Maybe a
Prelude.Nothing,
      $sel:platformLifecycleState:PlatformDescription' :: Maybe Text
platformLifecycleState = forall a. Maybe a
Prelude.Nothing,
      $sel:platformName:PlatformDescription' :: Maybe Text
platformName = forall a. Maybe a
Prelude.Nothing,
      $sel:platformOwner:PlatformDescription' :: Maybe Text
platformOwner = forall a. Maybe a
Prelude.Nothing,
      $sel:platformStatus:PlatformDescription' :: Maybe PlatformStatus
platformStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:platformVersion:PlatformDescription' :: Maybe Text
platformVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:programmingLanguages:PlatformDescription' :: Maybe [PlatformProgrammingLanguage]
programmingLanguages = forall a. Maybe a
Prelude.Nothing,
      $sel:solutionStackName:PlatformDescription' :: Maybe Text
solutionStackName = forall a. Maybe a
Prelude.Nothing,
      $sel:supportedAddonList:PlatformDescription' :: Maybe [Text]
supportedAddonList = forall a. Maybe a
Prelude.Nothing,
      $sel:supportedTierList:PlatformDescription' :: Maybe [Text]
supportedTierList = forall a. Maybe a
Prelude.Nothing
    }

-- | The custom AMIs supported by the platform version.
platformDescription_customAmiList :: Lens.Lens' PlatformDescription (Prelude.Maybe [CustomAmi])
platformDescription_customAmiList :: Lens' PlatformDescription (Maybe [CustomAmi])
platformDescription_customAmiList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlatformDescription' {Maybe [CustomAmi]
customAmiList :: Maybe [CustomAmi]
$sel:customAmiList:PlatformDescription' :: PlatformDescription -> Maybe [CustomAmi]
customAmiList} -> Maybe [CustomAmi]
customAmiList) (\s :: PlatformDescription
s@PlatformDescription' {} Maybe [CustomAmi]
a -> PlatformDescription
s {$sel:customAmiList:PlatformDescription' :: Maybe [CustomAmi]
customAmiList = Maybe [CustomAmi]
a} :: PlatformDescription) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The date when the platform version was created.
platformDescription_dateCreated :: Lens.Lens' PlatformDescription (Prelude.Maybe Prelude.UTCTime)
platformDescription_dateCreated :: Lens' PlatformDescription (Maybe UTCTime)
platformDescription_dateCreated = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlatformDescription' {Maybe ISO8601
dateCreated :: Maybe ISO8601
$sel:dateCreated:PlatformDescription' :: PlatformDescription -> Maybe ISO8601
dateCreated} -> Maybe ISO8601
dateCreated) (\s :: PlatformDescription
s@PlatformDescription' {} Maybe ISO8601
a -> PlatformDescription
s {$sel:dateCreated:PlatformDescription' :: Maybe ISO8601
dateCreated = Maybe ISO8601
a} :: PlatformDescription) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The date when the platform version was last updated.
platformDescription_dateUpdated :: Lens.Lens' PlatformDescription (Prelude.Maybe Prelude.UTCTime)
platformDescription_dateUpdated :: Lens' PlatformDescription (Maybe UTCTime)
platformDescription_dateUpdated = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlatformDescription' {Maybe ISO8601
dateUpdated :: Maybe ISO8601
$sel:dateUpdated:PlatformDescription' :: PlatformDescription -> Maybe ISO8601
dateUpdated} -> Maybe ISO8601
dateUpdated) (\s :: PlatformDescription
s@PlatformDescription' {} Maybe ISO8601
a -> PlatformDescription
s {$sel:dateUpdated:PlatformDescription' :: Maybe ISO8601
dateUpdated = Maybe ISO8601
a} :: PlatformDescription) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

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

-- | The frameworks supported by the platform version.
platformDescription_frameworks :: Lens.Lens' PlatformDescription (Prelude.Maybe [PlatformFramework])
platformDescription_frameworks :: Lens' PlatformDescription (Maybe [PlatformFramework])
platformDescription_frameworks = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlatformDescription' {Maybe [PlatformFramework]
frameworks :: Maybe [PlatformFramework]
$sel:frameworks:PlatformDescription' :: PlatformDescription -> Maybe [PlatformFramework]
frameworks} -> Maybe [PlatformFramework]
frameworks) (\s :: PlatformDescription
s@PlatformDescription' {} Maybe [PlatformFramework]
a -> PlatformDescription
s {$sel:frameworks:PlatformDescription' :: Maybe [PlatformFramework]
frameworks = Maybe [PlatformFramework]
a} :: PlatformDescription) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | Information about the maintainer of the platform version.
platformDescription_maintainer :: Lens.Lens' PlatformDescription (Prelude.Maybe Prelude.Text)
platformDescription_maintainer :: Lens' PlatformDescription (Maybe Text)
platformDescription_maintainer = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlatformDescription' {Maybe Text
maintainer :: Maybe Text
$sel:maintainer:PlatformDescription' :: PlatformDescription -> Maybe Text
maintainer} -> Maybe Text
maintainer) (\s :: PlatformDescription
s@PlatformDescription' {} Maybe Text
a -> PlatformDescription
s {$sel:maintainer:PlatformDescription' :: Maybe Text
maintainer = Maybe Text
a} :: PlatformDescription)

-- | The operating system used by the platform version.
platformDescription_operatingSystemName :: Lens.Lens' PlatformDescription (Prelude.Maybe Prelude.Text)
platformDescription_operatingSystemName :: Lens' PlatformDescription (Maybe Text)
platformDescription_operatingSystemName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlatformDescription' {Maybe Text
operatingSystemName :: Maybe Text
$sel:operatingSystemName:PlatformDescription' :: PlatformDescription -> Maybe Text
operatingSystemName} -> Maybe Text
operatingSystemName) (\s :: PlatformDescription
s@PlatformDescription' {} Maybe Text
a -> PlatformDescription
s {$sel:operatingSystemName:PlatformDescription' :: Maybe Text
operatingSystemName = Maybe Text
a} :: PlatformDescription)

-- | The version of the operating system used by the platform version.
platformDescription_operatingSystemVersion :: Lens.Lens' PlatformDescription (Prelude.Maybe Prelude.Text)
platformDescription_operatingSystemVersion :: Lens' PlatformDescription (Maybe Text)
platformDescription_operatingSystemVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlatformDescription' {Maybe Text
operatingSystemVersion :: Maybe Text
$sel:operatingSystemVersion:PlatformDescription' :: PlatformDescription -> Maybe Text
operatingSystemVersion} -> Maybe Text
operatingSystemVersion) (\s :: PlatformDescription
s@PlatformDescription' {} Maybe Text
a -> PlatformDescription
s {$sel:operatingSystemVersion:PlatformDescription' :: Maybe Text
operatingSystemVersion = Maybe Text
a} :: PlatformDescription)

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

-- | The state of the platform version\'s branch in its lifecycle.
--
-- Possible values: @Beta@ | @Supported@ | @Deprecated@ | @Retired@
platformDescription_platformBranchLifecycleState :: Lens.Lens' PlatformDescription (Prelude.Maybe Prelude.Text)
platformDescription_platformBranchLifecycleState :: Lens' PlatformDescription (Maybe Text)
platformDescription_platformBranchLifecycleState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlatformDescription' {Maybe Text
platformBranchLifecycleState :: Maybe Text
$sel:platformBranchLifecycleState:PlatformDescription' :: PlatformDescription -> Maybe Text
platformBranchLifecycleState} -> Maybe Text
platformBranchLifecycleState) (\s :: PlatformDescription
s@PlatformDescription' {} Maybe Text
a -> PlatformDescription
s {$sel:platformBranchLifecycleState:PlatformDescription' :: Maybe Text
platformBranchLifecycleState = Maybe Text
a} :: PlatformDescription)

-- | The platform branch to which the platform version belongs.
platformDescription_platformBranchName :: Lens.Lens' PlatformDescription (Prelude.Maybe Prelude.Text)
platformDescription_platformBranchName :: Lens' PlatformDescription (Maybe Text)
platformDescription_platformBranchName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlatformDescription' {Maybe Text
platformBranchName :: Maybe Text
$sel:platformBranchName:PlatformDescription' :: PlatformDescription -> Maybe Text
platformBranchName} -> Maybe Text
platformBranchName) (\s :: PlatformDescription
s@PlatformDescription' {} Maybe Text
a -> PlatformDescription
s {$sel:platformBranchName:PlatformDescription' :: Maybe Text
platformBranchName = Maybe Text
a} :: PlatformDescription)

-- | The category of the platform version.
platformDescription_platformCategory :: Lens.Lens' PlatformDescription (Prelude.Maybe Prelude.Text)
platformDescription_platformCategory :: Lens' PlatformDescription (Maybe Text)
platformDescription_platformCategory = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlatformDescription' {Maybe Text
platformCategory :: Maybe Text
$sel:platformCategory:PlatformDescription' :: PlatformDescription -> Maybe Text
platformCategory} -> Maybe Text
platformCategory) (\s :: PlatformDescription
s@PlatformDescription' {} Maybe Text
a -> PlatformDescription
s {$sel:platformCategory:PlatformDescription' :: Maybe Text
platformCategory = Maybe Text
a} :: PlatformDescription)

-- | The state of the platform version in its lifecycle.
--
-- Possible values: @Recommended@ | @null@
--
-- If a null value is returned, the platform version isn\'t the recommended
-- one for its branch. Each platform branch has a single recommended
-- platform version, typically the most recent one.
platformDescription_platformLifecycleState :: Lens.Lens' PlatformDescription (Prelude.Maybe Prelude.Text)
platformDescription_platformLifecycleState :: Lens' PlatformDescription (Maybe Text)
platformDescription_platformLifecycleState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlatformDescription' {Maybe Text
platformLifecycleState :: Maybe Text
$sel:platformLifecycleState:PlatformDescription' :: PlatformDescription -> Maybe Text
platformLifecycleState} -> Maybe Text
platformLifecycleState) (\s :: PlatformDescription
s@PlatformDescription' {} Maybe Text
a -> PlatformDescription
s {$sel:platformLifecycleState:PlatformDescription' :: Maybe Text
platformLifecycleState = Maybe Text
a} :: PlatformDescription)

-- | The name of the platform version.
platformDescription_platformName :: Lens.Lens' PlatformDescription (Prelude.Maybe Prelude.Text)
platformDescription_platformName :: Lens' PlatformDescription (Maybe Text)
platformDescription_platformName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlatformDescription' {Maybe Text
platformName :: Maybe Text
$sel:platformName:PlatformDescription' :: PlatformDescription -> Maybe Text
platformName} -> Maybe Text
platformName) (\s :: PlatformDescription
s@PlatformDescription' {} Maybe Text
a -> PlatformDescription
s {$sel:platformName:PlatformDescription' :: Maybe Text
platformName = Maybe Text
a} :: PlatformDescription)

-- | The AWS account ID of the person who created the platform version.
platformDescription_platformOwner :: Lens.Lens' PlatformDescription (Prelude.Maybe Prelude.Text)
platformDescription_platformOwner :: Lens' PlatformDescription (Maybe Text)
platformDescription_platformOwner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlatformDescription' {Maybe Text
platformOwner :: Maybe Text
$sel:platformOwner:PlatformDescription' :: PlatformDescription -> Maybe Text
platformOwner} -> Maybe Text
platformOwner) (\s :: PlatformDescription
s@PlatformDescription' {} Maybe Text
a -> PlatformDescription
s {$sel:platformOwner:PlatformDescription' :: Maybe Text
platformOwner = Maybe Text
a} :: PlatformDescription)

-- | The status of the platform version.
platformDescription_platformStatus :: Lens.Lens' PlatformDescription (Prelude.Maybe PlatformStatus)
platformDescription_platformStatus :: Lens' PlatformDescription (Maybe PlatformStatus)
platformDescription_platformStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlatformDescription' {Maybe PlatformStatus
platformStatus :: Maybe PlatformStatus
$sel:platformStatus:PlatformDescription' :: PlatformDescription -> Maybe PlatformStatus
platformStatus} -> Maybe PlatformStatus
platformStatus) (\s :: PlatformDescription
s@PlatformDescription' {} Maybe PlatformStatus
a -> PlatformDescription
s {$sel:platformStatus:PlatformDescription' :: Maybe PlatformStatus
platformStatus = Maybe PlatformStatus
a} :: PlatformDescription)

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

-- | The programming languages supported by the platform version.
platformDescription_programmingLanguages :: Lens.Lens' PlatformDescription (Prelude.Maybe [PlatformProgrammingLanguage])
platformDescription_programmingLanguages :: Lens' PlatformDescription (Maybe [PlatformProgrammingLanguage])
platformDescription_programmingLanguages = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlatformDescription' {Maybe [PlatformProgrammingLanguage]
programmingLanguages :: Maybe [PlatformProgrammingLanguage]
$sel:programmingLanguages:PlatformDescription' :: PlatformDescription -> Maybe [PlatformProgrammingLanguage]
programmingLanguages} -> Maybe [PlatformProgrammingLanguage]
programmingLanguages) (\s :: PlatformDescription
s@PlatformDescription' {} Maybe [PlatformProgrammingLanguage]
a -> PlatformDescription
s {$sel:programmingLanguages:PlatformDescription' :: Maybe [PlatformProgrammingLanguage]
programmingLanguages = Maybe [PlatformProgrammingLanguage]
a} :: PlatformDescription) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The name of the solution stack used by the platform version.
platformDescription_solutionStackName :: Lens.Lens' PlatformDescription (Prelude.Maybe Prelude.Text)
platformDescription_solutionStackName :: Lens' PlatformDescription (Maybe Text)
platformDescription_solutionStackName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlatformDescription' {Maybe Text
solutionStackName :: Maybe Text
$sel:solutionStackName:PlatformDescription' :: PlatformDescription -> Maybe Text
solutionStackName} -> Maybe Text
solutionStackName) (\s :: PlatformDescription
s@PlatformDescription' {} Maybe Text
a -> PlatformDescription
s {$sel:solutionStackName:PlatformDescription' :: Maybe Text
solutionStackName = Maybe Text
a} :: PlatformDescription)

-- | The additions supported by the platform version.
platformDescription_supportedAddonList :: Lens.Lens' PlatformDescription (Prelude.Maybe [Prelude.Text])
platformDescription_supportedAddonList :: Lens' PlatformDescription (Maybe [Text])
platformDescription_supportedAddonList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlatformDescription' {Maybe [Text]
supportedAddonList :: Maybe [Text]
$sel:supportedAddonList:PlatformDescription' :: PlatformDescription -> Maybe [Text]
supportedAddonList} -> Maybe [Text]
supportedAddonList) (\s :: PlatformDescription
s@PlatformDescription' {} Maybe [Text]
a -> PlatformDescription
s {$sel:supportedAddonList:PlatformDescription' :: Maybe [Text]
supportedAddonList = Maybe [Text]
a} :: PlatformDescription) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The tiers supported by the platform version.
platformDescription_supportedTierList :: Lens.Lens' PlatformDescription (Prelude.Maybe [Prelude.Text])
platformDescription_supportedTierList :: Lens' PlatformDescription (Maybe [Text])
platformDescription_supportedTierList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PlatformDescription' {Maybe [Text]
supportedTierList :: Maybe [Text]
$sel:supportedTierList:PlatformDescription' :: PlatformDescription -> Maybe [Text]
supportedTierList} -> Maybe [Text]
supportedTierList) (\s :: PlatformDescription
s@PlatformDescription' {} Maybe [Text]
a -> PlatformDescription
s {$sel:supportedTierList:PlatformDescription' :: Maybe [Text]
supportedTierList = Maybe [Text]
a} :: PlatformDescription) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Data.FromXML PlatformDescription where
  parseXML :: [Node] -> Either String PlatformDescription
parseXML [Node]
x =
    Maybe [CustomAmi]
-> Maybe ISO8601
-> Maybe ISO8601
-> Maybe Text
-> Maybe [PlatformFramework]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlatformStatus
-> Maybe Text
-> Maybe [PlatformProgrammingLanguage]
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> PlatformDescription
PlatformDescription'
      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
"CustomAmiList"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"DateCreated")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"DateUpdated")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Description")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Frameworks"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Maintainer")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"OperatingSystemName")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"OperatingSystemVersion")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PlatformArn")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PlatformBranchLifecycleState")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PlatformBranchName")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PlatformCategory")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PlatformLifecycleState")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PlatformName")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PlatformOwner")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PlatformStatus")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PlatformVersion")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ProgrammingLanguages"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"SolutionStackName")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"SupportedAddonList"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"SupportedTierList"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                  )

instance Prelude.Hashable PlatformDescription where
  hashWithSalt :: Int -> PlatformDescription -> Int
hashWithSalt Int
_salt PlatformDescription' {Maybe [Text]
Maybe [CustomAmi]
Maybe [PlatformFramework]
Maybe [PlatformProgrammingLanguage]
Maybe Text
Maybe ISO8601
Maybe PlatformStatus
supportedTierList :: Maybe [Text]
supportedAddonList :: Maybe [Text]
solutionStackName :: Maybe Text
programmingLanguages :: Maybe [PlatformProgrammingLanguage]
platformVersion :: Maybe Text
platformStatus :: Maybe PlatformStatus
platformOwner :: Maybe Text
platformName :: Maybe Text
platformLifecycleState :: Maybe Text
platformCategory :: Maybe Text
platformBranchName :: Maybe Text
platformBranchLifecycleState :: Maybe Text
platformArn :: Maybe Text
operatingSystemVersion :: Maybe Text
operatingSystemName :: Maybe Text
maintainer :: Maybe Text
frameworks :: Maybe [PlatformFramework]
description :: Maybe Text
dateUpdated :: Maybe ISO8601
dateCreated :: Maybe ISO8601
customAmiList :: Maybe [CustomAmi]
$sel:supportedTierList:PlatformDescription' :: PlatformDescription -> Maybe [Text]
$sel:supportedAddonList:PlatformDescription' :: PlatformDescription -> Maybe [Text]
$sel:solutionStackName:PlatformDescription' :: PlatformDescription -> Maybe Text
$sel:programmingLanguages:PlatformDescription' :: PlatformDescription -> Maybe [PlatformProgrammingLanguage]
$sel:platformVersion:PlatformDescription' :: PlatformDescription -> Maybe Text
$sel:platformStatus:PlatformDescription' :: PlatformDescription -> Maybe PlatformStatus
$sel:platformOwner:PlatformDescription' :: PlatformDescription -> Maybe Text
$sel:platformName:PlatformDescription' :: PlatformDescription -> Maybe Text
$sel:platformLifecycleState:PlatformDescription' :: PlatformDescription -> Maybe Text
$sel:platformCategory:PlatformDescription' :: PlatformDescription -> Maybe Text
$sel:platformBranchName:PlatformDescription' :: PlatformDescription -> Maybe Text
$sel:platformBranchLifecycleState:PlatformDescription' :: PlatformDescription -> Maybe Text
$sel:platformArn:PlatformDescription' :: PlatformDescription -> Maybe Text
$sel:operatingSystemVersion:PlatformDescription' :: PlatformDescription -> Maybe Text
$sel:operatingSystemName:PlatformDescription' :: PlatformDescription -> Maybe Text
$sel:maintainer:PlatformDescription' :: PlatformDescription -> Maybe Text
$sel:frameworks:PlatformDescription' :: PlatformDescription -> Maybe [PlatformFramework]
$sel:description:PlatformDescription' :: PlatformDescription -> Maybe Text
$sel:dateUpdated:PlatformDescription' :: PlatformDescription -> Maybe ISO8601
$sel:dateCreated:PlatformDescription' :: PlatformDescription -> Maybe ISO8601
$sel:customAmiList:PlatformDescription' :: PlatformDescription -> Maybe [CustomAmi]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [CustomAmi]
customAmiList
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
dateCreated
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
dateUpdated
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [PlatformFramework]
frameworks
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
maintainer
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
operatingSystemName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
operatingSystemVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
platformArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
platformBranchLifecycleState
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
platformBranchName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
platformCategory
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
platformLifecycleState
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
platformName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
platformOwner
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PlatformStatus
platformStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
platformVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [PlatformProgrammingLanguage]
programmingLanguages
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
solutionStackName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
supportedAddonList
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
supportedTierList

instance Prelude.NFData PlatformDescription where
  rnf :: PlatformDescription -> ()
rnf PlatformDescription' {Maybe [Text]
Maybe [CustomAmi]
Maybe [PlatformFramework]
Maybe [PlatformProgrammingLanguage]
Maybe Text
Maybe ISO8601
Maybe PlatformStatus
supportedTierList :: Maybe [Text]
supportedAddonList :: Maybe [Text]
solutionStackName :: Maybe Text
programmingLanguages :: Maybe [PlatformProgrammingLanguage]
platformVersion :: Maybe Text
platformStatus :: Maybe PlatformStatus
platformOwner :: Maybe Text
platformName :: Maybe Text
platformLifecycleState :: Maybe Text
platformCategory :: Maybe Text
platformBranchName :: Maybe Text
platformBranchLifecycleState :: Maybe Text
platformArn :: Maybe Text
operatingSystemVersion :: Maybe Text
operatingSystemName :: Maybe Text
maintainer :: Maybe Text
frameworks :: Maybe [PlatformFramework]
description :: Maybe Text
dateUpdated :: Maybe ISO8601
dateCreated :: Maybe ISO8601
customAmiList :: Maybe [CustomAmi]
$sel:supportedTierList:PlatformDescription' :: PlatformDescription -> Maybe [Text]
$sel:supportedAddonList:PlatformDescription' :: PlatformDescription -> Maybe [Text]
$sel:solutionStackName:PlatformDescription' :: PlatformDescription -> Maybe Text
$sel:programmingLanguages:PlatformDescription' :: PlatformDescription -> Maybe [PlatformProgrammingLanguage]
$sel:platformVersion:PlatformDescription' :: PlatformDescription -> Maybe Text
$sel:platformStatus:PlatformDescription' :: PlatformDescription -> Maybe PlatformStatus
$sel:platformOwner:PlatformDescription' :: PlatformDescription -> Maybe Text
$sel:platformName:PlatformDescription' :: PlatformDescription -> Maybe Text
$sel:platformLifecycleState:PlatformDescription' :: PlatformDescription -> Maybe Text
$sel:platformCategory:PlatformDescription' :: PlatformDescription -> Maybe Text
$sel:platformBranchName:PlatformDescription' :: PlatformDescription -> Maybe Text
$sel:platformBranchLifecycleState:PlatformDescription' :: PlatformDescription -> Maybe Text
$sel:platformArn:PlatformDescription' :: PlatformDescription -> Maybe Text
$sel:operatingSystemVersion:PlatformDescription' :: PlatformDescription -> Maybe Text
$sel:operatingSystemName:PlatformDescription' :: PlatformDescription -> Maybe Text
$sel:maintainer:PlatformDescription' :: PlatformDescription -> Maybe Text
$sel:frameworks:PlatformDescription' :: PlatformDescription -> Maybe [PlatformFramework]
$sel:description:PlatformDescription' :: PlatformDescription -> Maybe Text
$sel:dateUpdated:PlatformDescription' :: PlatformDescription -> Maybe ISO8601
$sel:dateCreated:PlatformDescription' :: PlatformDescription -> Maybe ISO8601
$sel:customAmiList:PlatformDescription' :: PlatformDescription -> Maybe [CustomAmi]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [CustomAmi]
customAmiList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
dateCreated
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
dateUpdated
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [PlatformFramework]
frameworks
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
maintainer
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
operatingSystemName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
operatingSystemVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
platformArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
platformBranchLifecycleState
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
platformBranchName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
platformCategory
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
platformLifecycleState
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
platformName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
platformOwner
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PlatformStatus
platformStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
platformVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [PlatformProgrammingLanguage]
programmingLanguages
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
solutionStackName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
supportedAddonList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [Text]
supportedTierList