{-# 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.ServiceCatalog.DescribeProvisionedProduct
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets information about the specified provisioned product.
module Amazonka.ServiceCatalog.DescribeProvisionedProduct
  ( -- * Creating a Request
    DescribeProvisionedProduct (..),
    newDescribeProvisionedProduct,

    -- * Request Lenses
    describeProvisionedProduct_acceptLanguage,
    describeProvisionedProduct_id,
    describeProvisionedProduct_name,

    -- * Destructuring the Response
    DescribeProvisionedProductResponse (..),
    newDescribeProvisionedProductResponse,

    -- * Response Lenses
    describeProvisionedProductResponse_cloudWatchDashboards,
    describeProvisionedProductResponse_provisionedProductDetail,
    describeProvisionedProductResponse_httpStatus,
  )
where

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
import Amazonka.ServiceCatalog.Types

-- | DescribeProvisionedProductAPI input structure. AcceptLanguage -
-- [Optional] The language code for localization. Id - [Optional] The
-- provisioned product identifier. Name - [Optional] Another provisioned
-- product identifier. Customers must provide either Id or Name.
--
-- /See:/ 'newDescribeProvisionedProduct' smart constructor.
data DescribeProvisionedProduct = DescribeProvisionedProduct'
  { -- | The language code.
    --
    -- -   @en@ - English (default)
    --
    -- -   @jp@ - Japanese
    --
    -- -   @zh@ - Chinese
    DescribeProvisionedProduct -> Maybe Text
acceptLanguage :: Prelude.Maybe Prelude.Text,
    -- | The provisioned product identifier. You must provide the name or ID, but
    -- not both.
    --
    -- If you do not provide a name or ID, or you provide both name and ID, an
    -- @InvalidParametersException@ will occur.
    DescribeProvisionedProduct -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The name of the provisioned product. You must provide the name or ID,
    -- but not both.
    --
    -- If you do not provide a name or ID, or you provide both name and ID, an
    -- @InvalidParametersException@ will occur.
    DescribeProvisionedProduct -> Maybe Text
name :: Prelude.Maybe Prelude.Text
  }
  deriving (DescribeProvisionedProduct -> DescribeProvisionedProduct -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeProvisionedProduct -> DescribeProvisionedProduct -> Bool
$c/= :: DescribeProvisionedProduct -> DescribeProvisionedProduct -> Bool
== :: DescribeProvisionedProduct -> DescribeProvisionedProduct -> Bool
$c== :: DescribeProvisionedProduct -> DescribeProvisionedProduct -> Bool
Prelude.Eq, ReadPrec [DescribeProvisionedProduct]
ReadPrec DescribeProvisionedProduct
Int -> ReadS DescribeProvisionedProduct
ReadS [DescribeProvisionedProduct]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeProvisionedProduct]
$creadListPrec :: ReadPrec [DescribeProvisionedProduct]
readPrec :: ReadPrec DescribeProvisionedProduct
$creadPrec :: ReadPrec DescribeProvisionedProduct
readList :: ReadS [DescribeProvisionedProduct]
$creadList :: ReadS [DescribeProvisionedProduct]
readsPrec :: Int -> ReadS DescribeProvisionedProduct
$creadsPrec :: Int -> ReadS DescribeProvisionedProduct
Prelude.Read, Int -> DescribeProvisionedProduct -> ShowS
[DescribeProvisionedProduct] -> ShowS
DescribeProvisionedProduct -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeProvisionedProduct] -> ShowS
$cshowList :: [DescribeProvisionedProduct] -> ShowS
show :: DescribeProvisionedProduct -> String
$cshow :: DescribeProvisionedProduct -> String
showsPrec :: Int -> DescribeProvisionedProduct -> ShowS
$cshowsPrec :: Int -> DescribeProvisionedProduct -> ShowS
Prelude.Show, forall x.
Rep DescribeProvisionedProduct x -> DescribeProvisionedProduct
forall x.
DescribeProvisionedProduct -> Rep DescribeProvisionedProduct x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeProvisionedProduct x -> DescribeProvisionedProduct
$cfrom :: forall x.
DescribeProvisionedProduct -> Rep DescribeProvisionedProduct x
Prelude.Generic)

-- |
-- Create a value of 'DescribeProvisionedProduct' 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:
--
-- 'acceptLanguage', 'describeProvisionedProduct_acceptLanguage' - The language code.
--
-- -   @en@ - English (default)
--
-- -   @jp@ - Japanese
--
-- -   @zh@ - Chinese
--
-- 'id', 'describeProvisionedProduct_id' - The provisioned product identifier. You must provide the name or ID, but
-- not both.
--
-- If you do not provide a name or ID, or you provide both name and ID, an
-- @InvalidParametersException@ will occur.
--
-- 'name', 'describeProvisionedProduct_name' - The name of the provisioned product. You must provide the name or ID,
-- but not both.
--
-- If you do not provide a name or ID, or you provide both name and ID, an
-- @InvalidParametersException@ will occur.
newDescribeProvisionedProduct ::
  DescribeProvisionedProduct
newDescribeProvisionedProduct :: DescribeProvisionedProduct
newDescribeProvisionedProduct =
  DescribeProvisionedProduct'
    { $sel:acceptLanguage:DescribeProvisionedProduct' :: Maybe Text
acceptLanguage =
        forall a. Maybe a
Prelude.Nothing,
      $sel:id:DescribeProvisionedProduct' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:name:DescribeProvisionedProduct' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing
    }

-- | The language code.
--
-- -   @en@ - English (default)
--
-- -   @jp@ - Japanese
--
-- -   @zh@ - Chinese
describeProvisionedProduct_acceptLanguage :: Lens.Lens' DescribeProvisionedProduct (Prelude.Maybe Prelude.Text)
describeProvisionedProduct_acceptLanguage :: Lens' DescribeProvisionedProduct (Maybe Text)
describeProvisionedProduct_acceptLanguage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProvisionedProduct' {Maybe Text
acceptLanguage :: Maybe Text
$sel:acceptLanguage:DescribeProvisionedProduct' :: DescribeProvisionedProduct -> Maybe Text
acceptLanguage} -> Maybe Text
acceptLanguage) (\s :: DescribeProvisionedProduct
s@DescribeProvisionedProduct' {} Maybe Text
a -> DescribeProvisionedProduct
s {$sel:acceptLanguage:DescribeProvisionedProduct' :: Maybe Text
acceptLanguage = Maybe Text
a} :: DescribeProvisionedProduct)

-- | The provisioned product identifier. You must provide the name or ID, but
-- not both.
--
-- If you do not provide a name or ID, or you provide both name and ID, an
-- @InvalidParametersException@ will occur.
describeProvisionedProduct_id :: Lens.Lens' DescribeProvisionedProduct (Prelude.Maybe Prelude.Text)
describeProvisionedProduct_id :: Lens' DescribeProvisionedProduct (Maybe Text)
describeProvisionedProduct_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProvisionedProduct' {Maybe Text
id :: Maybe Text
$sel:id:DescribeProvisionedProduct' :: DescribeProvisionedProduct -> Maybe Text
id} -> Maybe Text
id) (\s :: DescribeProvisionedProduct
s@DescribeProvisionedProduct' {} Maybe Text
a -> DescribeProvisionedProduct
s {$sel:id:DescribeProvisionedProduct' :: Maybe Text
id = Maybe Text
a} :: DescribeProvisionedProduct)

-- | The name of the provisioned product. You must provide the name or ID,
-- but not both.
--
-- If you do not provide a name or ID, or you provide both name and ID, an
-- @InvalidParametersException@ will occur.
describeProvisionedProduct_name :: Lens.Lens' DescribeProvisionedProduct (Prelude.Maybe Prelude.Text)
describeProvisionedProduct_name :: Lens' DescribeProvisionedProduct (Maybe Text)
describeProvisionedProduct_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProvisionedProduct' {Maybe Text
name :: Maybe Text
$sel:name:DescribeProvisionedProduct' :: DescribeProvisionedProduct -> Maybe Text
name} -> Maybe Text
name) (\s :: DescribeProvisionedProduct
s@DescribeProvisionedProduct' {} Maybe Text
a -> DescribeProvisionedProduct
s {$sel:name:DescribeProvisionedProduct' :: Maybe Text
name = Maybe Text
a} :: DescribeProvisionedProduct)

instance Core.AWSRequest DescribeProvisionedProduct where
  type
    AWSResponse DescribeProvisionedProduct =
      DescribeProvisionedProductResponse
  request :: (Service -> Service)
-> DescribeProvisionedProduct -> Request DescribeProvisionedProduct
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeProvisionedProduct
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeProvisionedProduct)))
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 [CloudWatchDashboard]
-> Maybe ProvisionedProductDetail
-> Int
-> DescribeProvisionedProductResponse
DescribeProvisionedProductResponse'
            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
"CloudWatchDashboards"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            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
"ProvisionedProductDetail")
            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 DescribeProvisionedProduct where
  hashWithSalt :: Int -> DescribeProvisionedProduct -> Int
hashWithSalt Int
_salt DescribeProvisionedProduct' {Maybe Text
name :: Maybe Text
id :: Maybe Text
acceptLanguage :: Maybe Text
$sel:name:DescribeProvisionedProduct' :: DescribeProvisionedProduct -> Maybe Text
$sel:id:DescribeProvisionedProduct' :: DescribeProvisionedProduct -> Maybe Text
$sel:acceptLanguage:DescribeProvisionedProduct' :: DescribeProvisionedProduct -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
acceptLanguage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name

instance Prelude.NFData DescribeProvisionedProduct where
  rnf :: DescribeProvisionedProduct -> ()
rnf DescribeProvisionedProduct' {Maybe Text
name :: Maybe Text
id :: Maybe Text
acceptLanguage :: Maybe Text
$sel:name:DescribeProvisionedProduct' :: DescribeProvisionedProduct -> Maybe Text
$sel:id:DescribeProvisionedProduct' :: DescribeProvisionedProduct -> Maybe Text
$sel:acceptLanguage:DescribeProvisionedProduct' :: DescribeProvisionedProduct -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
acceptLanguage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name

instance Data.ToHeaders DescribeProvisionedProduct where
  toHeaders :: DescribeProvisionedProduct -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AWS242ServiceCatalogService.DescribeProvisionedProduct" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DescribeProvisionedProduct where
  toJSON :: DescribeProvisionedProduct -> Value
toJSON DescribeProvisionedProduct' {Maybe Text
name :: Maybe Text
id :: Maybe Text
acceptLanguage :: Maybe Text
$sel:name:DescribeProvisionedProduct' :: DescribeProvisionedProduct -> Maybe Text
$sel:id:DescribeProvisionedProduct' :: DescribeProvisionedProduct -> Maybe Text
$sel:acceptLanguage:DescribeProvisionedProduct' :: DescribeProvisionedProduct -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AcceptLanguage" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
acceptLanguage,
            (Key
"Id" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
id,
            (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
name
          ]
      )

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

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

-- | /See:/ 'newDescribeProvisionedProductResponse' smart constructor.
data DescribeProvisionedProductResponse = DescribeProvisionedProductResponse'
  { -- | Any CloudWatch dashboards that were created when provisioning the
    -- product.
    DescribeProvisionedProductResponse -> Maybe [CloudWatchDashboard]
cloudWatchDashboards :: Prelude.Maybe [CloudWatchDashboard],
    -- | Information about the provisioned product.
    DescribeProvisionedProductResponse
-> Maybe ProvisionedProductDetail
provisionedProductDetail :: Prelude.Maybe ProvisionedProductDetail,
    -- | The response's http status code.
    DescribeProvisionedProductResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeProvisionedProductResponse
-> DescribeProvisionedProductResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeProvisionedProductResponse
-> DescribeProvisionedProductResponse -> Bool
$c/= :: DescribeProvisionedProductResponse
-> DescribeProvisionedProductResponse -> Bool
== :: DescribeProvisionedProductResponse
-> DescribeProvisionedProductResponse -> Bool
$c== :: DescribeProvisionedProductResponse
-> DescribeProvisionedProductResponse -> Bool
Prelude.Eq, ReadPrec [DescribeProvisionedProductResponse]
ReadPrec DescribeProvisionedProductResponse
Int -> ReadS DescribeProvisionedProductResponse
ReadS [DescribeProvisionedProductResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeProvisionedProductResponse]
$creadListPrec :: ReadPrec [DescribeProvisionedProductResponse]
readPrec :: ReadPrec DescribeProvisionedProductResponse
$creadPrec :: ReadPrec DescribeProvisionedProductResponse
readList :: ReadS [DescribeProvisionedProductResponse]
$creadList :: ReadS [DescribeProvisionedProductResponse]
readsPrec :: Int -> ReadS DescribeProvisionedProductResponse
$creadsPrec :: Int -> ReadS DescribeProvisionedProductResponse
Prelude.Read, Int -> DescribeProvisionedProductResponse -> ShowS
[DescribeProvisionedProductResponse] -> ShowS
DescribeProvisionedProductResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeProvisionedProductResponse] -> ShowS
$cshowList :: [DescribeProvisionedProductResponse] -> ShowS
show :: DescribeProvisionedProductResponse -> String
$cshow :: DescribeProvisionedProductResponse -> String
showsPrec :: Int -> DescribeProvisionedProductResponse -> ShowS
$cshowsPrec :: Int -> DescribeProvisionedProductResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeProvisionedProductResponse x
-> DescribeProvisionedProductResponse
forall x.
DescribeProvisionedProductResponse
-> Rep DescribeProvisionedProductResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeProvisionedProductResponse x
-> DescribeProvisionedProductResponse
$cfrom :: forall x.
DescribeProvisionedProductResponse
-> Rep DescribeProvisionedProductResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeProvisionedProductResponse' 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:
--
-- 'cloudWatchDashboards', 'describeProvisionedProductResponse_cloudWatchDashboards' - Any CloudWatch dashboards that were created when provisioning the
-- product.
--
-- 'provisionedProductDetail', 'describeProvisionedProductResponse_provisionedProductDetail' - Information about the provisioned product.
--
-- 'httpStatus', 'describeProvisionedProductResponse_httpStatus' - The response's http status code.
newDescribeProvisionedProductResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeProvisionedProductResponse
newDescribeProvisionedProductResponse :: Int -> DescribeProvisionedProductResponse
newDescribeProvisionedProductResponse Int
pHttpStatus_ =
  DescribeProvisionedProductResponse'
    { $sel:cloudWatchDashboards:DescribeProvisionedProductResponse' :: Maybe [CloudWatchDashboard]
cloudWatchDashboards =
        forall a. Maybe a
Prelude.Nothing,
      $sel:provisionedProductDetail:DescribeProvisionedProductResponse' :: Maybe ProvisionedProductDetail
provisionedProductDetail =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeProvisionedProductResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Any CloudWatch dashboards that were created when provisioning the
-- product.
describeProvisionedProductResponse_cloudWatchDashboards :: Lens.Lens' DescribeProvisionedProductResponse (Prelude.Maybe [CloudWatchDashboard])
describeProvisionedProductResponse_cloudWatchDashboards :: Lens'
  DescribeProvisionedProductResponse (Maybe [CloudWatchDashboard])
describeProvisionedProductResponse_cloudWatchDashboards = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProvisionedProductResponse' {Maybe [CloudWatchDashboard]
cloudWatchDashboards :: Maybe [CloudWatchDashboard]
$sel:cloudWatchDashboards:DescribeProvisionedProductResponse' :: DescribeProvisionedProductResponse -> Maybe [CloudWatchDashboard]
cloudWatchDashboards} -> Maybe [CloudWatchDashboard]
cloudWatchDashboards) (\s :: DescribeProvisionedProductResponse
s@DescribeProvisionedProductResponse' {} Maybe [CloudWatchDashboard]
a -> DescribeProvisionedProductResponse
s {$sel:cloudWatchDashboards:DescribeProvisionedProductResponse' :: Maybe [CloudWatchDashboard]
cloudWatchDashboards = Maybe [CloudWatchDashboard]
a} :: DescribeProvisionedProductResponse) 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 provisioned product.
describeProvisionedProductResponse_provisionedProductDetail :: Lens.Lens' DescribeProvisionedProductResponse (Prelude.Maybe ProvisionedProductDetail)
describeProvisionedProductResponse_provisionedProductDetail :: Lens'
  DescribeProvisionedProductResponse (Maybe ProvisionedProductDetail)
describeProvisionedProductResponse_provisionedProductDetail = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProvisionedProductResponse' {Maybe ProvisionedProductDetail
provisionedProductDetail :: Maybe ProvisionedProductDetail
$sel:provisionedProductDetail:DescribeProvisionedProductResponse' :: DescribeProvisionedProductResponse
-> Maybe ProvisionedProductDetail
provisionedProductDetail} -> Maybe ProvisionedProductDetail
provisionedProductDetail) (\s :: DescribeProvisionedProductResponse
s@DescribeProvisionedProductResponse' {} Maybe ProvisionedProductDetail
a -> DescribeProvisionedProductResponse
s {$sel:provisionedProductDetail:DescribeProvisionedProductResponse' :: Maybe ProvisionedProductDetail
provisionedProductDetail = Maybe ProvisionedProductDetail
a} :: DescribeProvisionedProductResponse)

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

instance
  Prelude.NFData
    DescribeProvisionedProductResponse
  where
  rnf :: DescribeProvisionedProductResponse -> ()
rnf DescribeProvisionedProductResponse' {Int
Maybe [CloudWatchDashboard]
Maybe ProvisionedProductDetail
httpStatus :: Int
provisionedProductDetail :: Maybe ProvisionedProductDetail
cloudWatchDashboards :: Maybe [CloudWatchDashboard]
$sel:httpStatus:DescribeProvisionedProductResponse' :: DescribeProvisionedProductResponse -> Int
$sel:provisionedProductDetail:DescribeProvisionedProductResponse' :: DescribeProvisionedProductResponse
-> Maybe ProvisionedProductDetail
$sel:cloudWatchDashboards:DescribeProvisionedProductResponse' :: DescribeProvisionedProductResponse -> Maybe [CloudWatchDashboard]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [CloudWatchDashboard]
cloudWatchDashboards
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ProvisionedProductDetail
provisionedProductDetail
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus