{-# 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.EKS.DescribeAddonConfiguration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns configuration options.
module Amazonka.EKS.DescribeAddonConfiguration
  ( -- * Creating a Request
    DescribeAddonConfiguration (..),
    newDescribeAddonConfiguration,

    -- * Request Lenses
    describeAddonConfiguration_addonName,
    describeAddonConfiguration_addonVersion,

    -- * Destructuring the Response
    DescribeAddonConfigurationResponse (..),
    newDescribeAddonConfigurationResponse,

    -- * Response Lenses
    describeAddonConfigurationResponse_addonName,
    describeAddonConfigurationResponse_addonVersion,
    describeAddonConfigurationResponse_configurationSchema,
    describeAddonConfigurationResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDescribeAddonConfiguration' smart constructor.
data DescribeAddonConfiguration = DescribeAddonConfiguration'
  { -- | The name of the add-on. The name must match one of the names that
    -- <https://docs.aws.amazon.com/eks/latest/APIReference/API_DescribeAddonVersions.html DescribeAddonVersions>
    -- returns.
    DescribeAddonConfiguration -> Text
addonName :: Prelude.Text,
    -- | The version of the add-on. The version must match one of the versions
    -- returned by
    -- <https://docs.aws.amazon.com/eks/latest/APIReference/API_DescribeAddonVersions.html DescribeAddonVersions>
    -- .
    DescribeAddonConfiguration -> Text
addonVersion :: Prelude.Text
  }
  deriving (DescribeAddonConfiguration -> DescribeAddonConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeAddonConfiguration -> DescribeAddonConfiguration -> Bool
$c/= :: DescribeAddonConfiguration -> DescribeAddonConfiguration -> Bool
== :: DescribeAddonConfiguration -> DescribeAddonConfiguration -> Bool
$c== :: DescribeAddonConfiguration -> DescribeAddonConfiguration -> Bool
Prelude.Eq, ReadPrec [DescribeAddonConfiguration]
ReadPrec DescribeAddonConfiguration
Int -> ReadS DescribeAddonConfiguration
ReadS [DescribeAddonConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeAddonConfiguration]
$creadListPrec :: ReadPrec [DescribeAddonConfiguration]
readPrec :: ReadPrec DescribeAddonConfiguration
$creadPrec :: ReadPrec DescribeAddonConfiguration
readList :: ReadS [DescribeAddonConfiguration]
$creadList :: ReadS [DescribeAddonConfiguration]
readsPrec :: Int -> ReadS DescribeAddonConfiguration
$creadsPrec :: Int -> ReadS DescribeAddonConfiguration
Prelude.Read, Int -> DescribeAddonConfiguration -> ShowS
[DescribeAddonConfiguration] -> ShowS
DescribeAddonConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeAddonConfiguration] -> ShowS
$cshowList :: [DescribeAddonConfiguration] -> ShowS
show :: DescribeAddonConfiguration -> String
$cshow :: DescribeAddonConfiguration -> String
showsPrec :: Int -> DescribeAddonConfiguration -> ShowS
$cshowsPrec :: Int -> DescribeAddonConfiguration -> ShowS
Prelude.Show, forall x.
Rep DescribeAddonConfiguration x -> DescribeAddonConfiguration
forall x.
DescribeAddonConfiguration -> Rep DescribeAddonConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeAddonConfiguration x -> DescribeAddonConfiguration
$cfrom :: forall x.
DescribeAddonConfiguration -> Rep DescribeAddonConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'DescribeAddonConfiguration' 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:
--
-- 'addonName', 'describeAddonConfiguration_addonName' - The name of the add-on. The name must match one of the names that
-- <https://docs.aws.amazon.com/eks/latest/APIReference/API_DescribeAddonVersions.html DescribeAddonVersions>
-- returns.
--
-- 'addonVersion', 'describeAddonConfiguration_addonVersion' - The version of the add-on. The version must match one of the versions
-- returned by
-- <https://docs.aws.amazon.com/eks/latest/APIReference/API_DescribeAddonVersions.html DescribeAddonVersions>
-- .
newDescribeAddonConfiguration ::
  -- | 'addonName'
  Prelude.Text ->
  -- | 'addonVersion'
  Prelude.Text ->
  DescribeAddonConfiguration
newDescribeAddonConfiguration :: Text -> Text -> DescribeAddonConfiguration
newDescribeAddonConfiguration
  Text
pAddonName_
  Text
pAddonVersion_ =
    DescribeAddonConfiguration'
      { $sel:addonName:DescribeAddonConfiguration' :: Text
addonName =
          Text
pAddonName_,
        $sel:addonVersion:DescribeAddonConfiguration' :: Text
addonVersion = Text
pAddonVersion_
      }

-- | The name of the add-on. The name must match one of the names that
-- <https://docs.aws.amazon.com/eks/latest/APIReference/API_DescribeAddonVersions.html DescribeAddonVersions>
-- returns.
describeAddonConfiguration_addonName :: Lens.Lens' DescribeAddonConfiguration Prelude.Text
describeAddonConfiguration_addonName :: Lens' DescribeAddonConfiguration Text
describeAddonConfiguration_addonName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAddonConfiguration' {Text
addonName :: Text
$sel:addonName:DescribeAddonConfiguration' :: DescribeAddonConfiguration -> Text
addonName} -> Text
addonName) (\s :: DescribeAddonConfiguration
s@DescribeAddonConfiguration' {} Text
a -> DescribeAddonConfiguration
s {$sel:addonName:DescribeAddonConfiguration' :: Text
addonName = Text
a} :: DescribeAddonConfiguration)

-- | The version of the add-on. The version must match one of the versions
-- returned by
-- <https://docs.aws.amazon.com/eks/latest/APIReference/API_DescribeAddonVersions.html DescribeAddonVersions>
-- .
describeAddonConfiguration_addonVersion :: Lens.Lens' DescribeAddonConfiguration Prelude.Text
describeAddonConfiguration_addonVersion :: Lens' DescribeAddonConfiguration Text
describeAddonConfiguration_addonVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAddonConfiguration' {Text
addonVersion :: Text
$sel:addonVersion:DescribeAddonConfiguration' :: DescribeAddonConfiguration -> Text
addonVersion} -> Text
addonVersion) (\s :: DescribeAddonConfiguration
s@DescribeAddonConfiguration' {} Text
a -> DescribeAddonConfiguration
s {$sel:addonVersion:DescribeAddonConfiguration' :: Text
addonVersion = Text
a} :: DescribeAddonConfiguration)

instance Core.AWSRequest DescribeAddonConfiguration where
  type
    AWSResponse DescribeAddonConfiguration =
      DescribeAddonConfigurationResponse
  request :: (Service -> Service)
-> DescribeAddonConfiguration -> Request DescribeAddonConfiguration
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 DescribeAddonConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeAddonConfiguration)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe Text
-> Int
-> DescribeAddonConfigurationResponse
DescribeAddonConfigurationResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"addonName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"addonVersion")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"configurationSchema")
            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 DescribeAddonConfiguration where
  hashWithSalt :: Int -> DescribeAddonConfiguration -> Int
hashWithSalt Int
_salt DescribeAddonConfiguration' {Text
addonVersion :: Text
addonName :: Text
$sel:addonVersion:DescribeAddonConfiguration' :: DescribeAddonConfiguration -> Text
$sel:addonName:DescribeAddonConfiguration' :: DescribeAddonConfiguration -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
addonName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
addonVersion

instance Prelude.NFData DescribeAddonConfiguration where
  rnf :: DescribeAddonConfiguration -> ()
rnf DescribeAddonConfiguration' {Text
addonVersion :: Text
addonName :: Text
$sel:addonVersion:DescribeAddonConfiguration' :: DescribeAddonConfiguration -> Text
$sel:addonName:DescribeAddonConfiguration' :: DescribeAddonConfiguration -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
addonName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
addonVersion

instance Data.ToHeaders DescribeAddonConfiguration where
  toHeaders :: DescribeAddonConfiguration -> 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 DescribeAddonConfiguration where
  toPath :: DescribeAddonConfiguration -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const ByteString
"/addons/configuration-schemas"

instance Data.ToQuery DescribeAddonConfiguration where
  toQuery :: DescribeAddonConfiguration -> QueryString
toQuery DescribeAddonConfiguration' {Text
addonVersion :: Text
addonName :: Text
$sel:addonVersion:DescribeAddonConfiguration' :: DescribeAddonConfiguration -> Text
$sel:addonName:DescribeAddonConfiguration' :: DescribeAddonConfiguration -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"addonName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
addonName,
        ByteString
"addonVersion" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
addonVersion
      ]

-- | /See:/ 'newDescribeAddonConfigurationResponse' smart constructor.
data DescribeAddonConfigurationResponse = DescribeAddonConfigurationResponse'
  { -- | The name of the add-on.
    DescribeAddonConfigurationResponse -> Maybe Text
addonName :: Prelude.Maybe Prelude.Text,
    -- | The version of the add-on. The version must match one of the versions
    -- returned by
    -- <https://docs.aws.amazon.com/eks/latest/APIReference/API_DescribeAddonVersions.html DescribeAddonVersions>
    -- .
    DescribeAddonConfigurationResponse -> Maybe Text
addonVersion :: Prelude.Maybe Prelude.Text,
    -- | A JSON schema that\'s used to validate the configuration values that you
    -- provide when an addon is created or updated.
    DescribeAddonConfigurationResponse -> Maybe Text
configurationSchema :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeAddonConfigurationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeAddonConfigurationResponse
-> DescribeAddonConfigurationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeAddonConfigurationResponse
-> DescribeAddonConfigurationResponse -> Bool
$c/= :: DescribeAddonConfigurationResponse
-> DescribeAddonConfigurationResponse -> Bool
== :: DescribeAddonConfigurationResponse
-> DescribeAddonConfigurationResponse -> Bool
$c== :: DescribeAddonConfigurationResponse
-> DescribeAddonConfigurationResponse -> Bool
Prelude.Eq, ReadPrec [DescribeAddonConfigurationResponse]
ReadPrec DescribeAddonConfigurationResponse
Int -> ReadS DescribeAddonConfigurationResponse
ReadS [DescribeAddonConfigurationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeAddonConfigurationResponse]
$creadListPrec :: ReadPrec [DescribeAddonConfigurationResponse]
readPrec :: ReadPrec DescribeAddonConfigurationResponse
$creadPrec :: ReadPrec DescribeAddonConfigurationResponse
readList :: ReadS [DescribeAddonConfigurationResponse]
$creadList :: ReadS [DescribeAddonConfigurationResponse]
readsPrec :: Int -> ReadS DescribeAddonConfigurationResponse
$creadsPrec :: Int -> ReadS DescribeAddonConfigurationResponse
Prelude.Read, Int -> DescribeAddonConfigurationResponse -> ShowS
[DescribeAddonConfigurationResponse] -> ShowS
DescribeAddonConfigurationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeAddonConfigurationResponse] -> ShowS
$cshowList :: [DescribeAddonConfigurationResponse] -> ShowS
show :: DescribeAddonConfigurationResponse -> String
$cshow :: DescribeAddonConfigurationResponse -> String
showsPrec :: Int -> DescribeAddonConfigurationResponse -> ShowS
$cshowsPrec :: Int -> DescribeAddonConfigurationResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeAddonConfigurationResponse x
-> DescribeAddonConfigurationResponse
forall x.
DescribeAddonConfigurationResponse
-> Rep DescribeAddonConfigurationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeAddonConfigurationResponse x
-> DescribeAddonConfigurationResponse
$cfrom :: forall x.
DescribeAddonConfigurationResponse
-> Rep DescribeAddonConfigurationResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeAddonConfigurationResponse' 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:
--
-- 'addonName', 'describeAddonConfigurationResponse_addonName' - The name of the add-on.
--
-- 'addonVersion', 'describeAddonConfigurationResponse_addonVersion' - The version of the add-on. The version must match one of the versions
-- returned by
-- <https://docs.aws.amazon.com/eks/latest/APIReference/API_DescribeAddonVersions.html DescribeAddonVersions>
-- .
--
-- 'configurationSchema', 'describeAddonConfigurationResponse_configurationSchema' - A JSON schema that\'s used to validate the configuration values that you
-- provide when an addon is created or updated.
--
-- 'httpStatus', 'describeAddonConfigurationResponse_httpStatus' - The response's http status code.
newDescribeAddonConfigurationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeAddonConfigurationResponse
newDescribeAddonConfigurationResponse :: Int -> DescribeAddonConfigurationResponse
newDescribeAddonConfigurationResponse Int
pHttpStatus_ =
  DescribeAddonConfigurationResponse'
    { $sel:addonName:DescribeAddonConfigurationResponse' :: Maybe Text
addonName =
        forall a. Maybe a
Prelude.Nothing,
      $sel:addonVersion:DescribeAddonConfigurationResponse' :: Maybe Text
addonVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:configurationSchema:DescribeAddonConfigurationResponse' :: Maybe Text
configurationSchema = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeAddonConfigurationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The name of the add-on.
describeAddonConfigurationResponse_addonName :: Lens.Lens' DescribeAddonConfigurationResponse (Prelude.Maybe Prelude.Text)
describeAddonConfigurationResponse_addonName :: Lens' DescribeAddonConfigurationResponse (Maybe Text)
describeAddonConfigurationResponse_addonName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAddonConfigurationResponse' {Maybe Text
addonName :: Maybe Text
$sel:addonName:DescribeAddonConfigurationResponse' :: DescribeAddonConfigurationResponse -> Maybe Text
addonName} -> Maybe Text
addonName) (\s :: DescribeAddonConfigurationResponse
s@DescribeAddonConfigurationResponse' {} Maybe Text
a -> DescribeAddonConfigurationResponse
s {$sel:addonName:DescribeAddonConfigurationResponse' :: Maybe Text
addonName = Maybe Text
a} :: DescribeAddonConfigurationResponse)

-- | The version of the add-on. The version must match one of the versions
-- returned by
-- <https://docs.aws.amazon.com/eks/latest/APIReference/API_DescribeAddonVersions.html DescribeAddonVersions>
-- .
describeAddonConfigurationResponse_addonVersion :: Lens.Lens' DescribeAddonConfigurationResponse (Prelude.Maybe Prelude.Text)
describeAddonConfigurationResponse_addonVersion :: Lens' DescribeAddonConfigurationResponse (Maybe Text)
describeAddonConfigurationResponse_addonVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAddonConfigurationResponse' {Maybe Text
addonVersion :: Maybe Text
$sel:addonVersion:DescribeAddonConfigurationResponse' :: DescribeAddonConfigurationResponse -> Maybe Text
addonVersion} -> Maybe Text
addonVersion) (\s :: DescribeAddonConfigurationResponse
s@DescribeAddonConfigurationResponse' {} Maybe Text
a -> DescribeAddonConfigurationResponse
s {$sel:addonVersion:DescribeAddonConfigurationResponse' :: Maybe Text
addonVersion = Maybe Text
a} :: DescribeAddonConfigurationResponse)

-- | A JSON schema that\'s used to validate the configuration values that you
-- provide when an addon is created or updated.
describeAddonConfigurationResponse_configurationSchema :: Lens.Lens' DescribeAddonConfigurationResponse (Prelude.Maybe Prelude.Text)
describeAddonConfigurationResponse_configurationSchema :: Lens' DescribeAddonConfigurationResponse (Maybe Text)
describeAddonConfigurationResponse_configurationSchema = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAddonConfigurationResponse' {Maybe Text
configurationSchema :: Maybe Text
$sel:configurationSchema:DescribeAddonConfigurationResponse' :: DescribeAddonConfigurationResponse -> Maybe Text
configurationSchema} -> Maybe Text
configurationSchema) (\s :: DescribeAddonConfigurationResponse
s@DescribeAddonConfigurationResponse' {} Maybe Text
a -> DescribeAddonConfigurationResponse
s {$sel:configurationSchema:DescribeAddonConfigurationResponse' :: Maybe Text
configurationSchema = Maybe Text
a} :: DescribeAddonConfigurationResponse)

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

instance
  Prelude.NFData
    DescribeAddonConfigurationResponse
  where
  rnf :: DescribeAddonConfigurationResponse -> ()
rnf DescribeAddonConfigurationResponse' {Int
Maybe Text
httpStatus :: Int
configurationSchema :: Maybe Text
addonVersion :: Maybe Text
addonName :: Maybe Text
$sel:httpStatus:DescribeAddonConfigurationResponse' :: DescribeAddonConfigurationResponse -> Int
$sel:configurationSchema:DescribeAddonConfigurationResponse' :: DescribeAddonConfigurationResponse -> Maybe Text
$sel:addonVersion:DescribeAddonConfigurationResponse' :: DescribeAddonConfigurationResponse -> Maybe Text
$sel:addonName:DescribeAddonConfigurationResponse' :: DescribeAddonConfigurationResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
addonName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
addonVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
configurationSchema
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus