{-# 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.IoTSiteWise.DescribeAssetProperty
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves information about an asset property.
--
-- When you call this operation for an attribute property, this response
-- includes the default attribute value that you define in the asset model.
-- If you update the default value in the model, this operation\'s response
-- includes the new default value.
--
-- This operation doesn\'t return the value of the asset property. To get
-- the value of an asset property, use
-- <https://docs.aws.amazon.com/iot-sitewise/latest/APIReference/API_GetAssetPropertyValue.html GetAssetPropertyValue>.
module Amazonka.IoTSiteWise.DescribeAssetProperty
  ( -- * Creating a Request
    DescribeAssetProperty (..),
    newDescribeAssetProperty,

    -- * Request Lenses
    describeAssetProperty_assetId,
    describeAssetProperty_propertyId,

    -- * Destructuring the Response
    DescribeAssetPropertyResponse (..),
    newDescribeAssetPropertyResponse,

    -- * Response Lenses
    describeAssetPropertyResponse_assetProperty,
    describeAssetPropertyResponse_compositeModel,
    describeAssetPropertyResponse_httpStatus,
    describeAssetPropertyResponse_assetId,
    describeAssetPropertyResponse_assetName,
    describeAssetPropertyResponse_assetModelId,
  )
where

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

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

-- |
-- Create a value of 'DescribeAssetProperty' 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:
--
-- 'assetId', 'describeAssetProperty_assetId' - The ID of the asset.
--
-- 'propertyId', 'describeAssetProperty_propertyId' - The ID of the asset property.
newDescribeAssetProperty ::
  -- | 'assetId'
  Prelude.Text ->
  -- | 'propertyId'
  Prelude.Text ->
  DescribeAssetProperty
newDescribeAssetProperty :: Text -> Text -> DescribeAssetProperty
newDescribeAssetProperty Text
pAssetId_ Text
pPropertyId_ =
  DescribeAssetProperty'
    { $sel:assetId:DescribeAssetProperty' :: Text
assetId = Text
pAssetId_,
      $sel:propertyId:DescribeAssetProperty' :: Text
propertyId = Text
pPropertyId_
    }

-- | The ID of the asset.
describeAssetProperty_assetId :: Lens.Lens' DescribeAssetProperty Prelude.Text
describeAssetProperty_assetId :: Lens' DescribeAssetProperty Text
describeAssetProperty_assetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAssetProperty' {Text
assetId :: Text
$sel:assetId:DescribeAssetProperty' :: DescribeAssetProperty -> Text
assetId} -> Text
assetId) (\s :: DescribeAssetProperty
s@DescribeAssetProperty' {} Text
a -> DescribeAssetProperty
s {$sel:assetId:DescribeAssetProperty' :: Text
assetId = Text
a} :: DescribeAssetProperty)

-- | The ID of the asset property.
describeAssetProperty_propertyId :: Lens.Lens' DescribeAssetProperty Prelude.Text
describeAssetProperty_propertyId :: Lens' DescribeAssetProperty Text
describeAssetProperty_propertyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAssetProperty' {Text
propertyId :: Text
$sel:propertyId:DescribeAssetProperty' :: DescribeAssetProperty -> Text
propertyId} -> Text
propertyId) (\s :: DescribeAssetProperty
s@DescribeAssetProperty' {} Text
a -> DescribeAssetProperty
s {$sel:propertyId:DescribeAssetProperty' :: Text
propertyId = Text
a} :: DescribeAssetProperty)

instance Core.AWSRequest DescribeAssetProperty where
  type
    AWSResponse DescribeAssetProperty =
      DescribeAssetPropertyResponse
  request :: (Service -> Service)
-> DescribeAssetProperty -> Request DescribeAssetProperty
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 DescribeAssetProperty
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeAssetProperty)))
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 Property
-> Maybe CompositeModelProperty
-> Int
-> Text
-> Text
-> Text
-> DescribeAssetPropertyResponse
DescribeAssetPropertyResponse'
            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
"assetProperty")
            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
"compositeModel")
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"assetId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"assetName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"assetModelId")
      )

instance Prelude.Hashable DescribeAssetProperty where
  hashWithSalt :: Int -> DescribeAssetProperty -> Int
hashWithSalt Int
_salt DescribeAssetProperty' {Text
propertyId :: Text
assetId :: Text
$sel:propertyId:DescribeAssetProperty' :: DescribeAssetProperty -> Text
$sel:assetId:DescribeAssetProperty' :: DescribeAssetProperty -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
assetId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
propertyId

instance Prelude.NFData DescribeAssetProperty where
  rnf :: DescribeAssetProperty -> ()
rnf DescribeAssetProperty' {Text
propertyId :: Text
assetId :: Text
$sel:propertyId:DescribeAssetProperty' :: DescribeAssetProperty -> Text
$sel:assetId:DescribeAssetProperty' :: DescribeAssetProperty -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
assetId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
propertyId

instance Data.ToHeaders DescribeAssetProperty where
  toHeaders :: DescribeAssetProperty -> 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 DescribeAssetProperty where
  toPath :: DescribeAssetProperty -> ByteString
toPath DescribeAssetProperty' {Text
propertyId :: Text
assetId :: Text
$sel:propertyId:DescribeAssetProperty' :: DescribeAssetProperty -> Text
$sel:assetId:DescribeAssetProperty' :: DescribeAssetProperty -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/assets/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
assetId,
        ByteString
"/properties/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
propertyId
      ]

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

-- | /See:/ 'newDescribeAssetPropertyResponse' smart constructor.
data DescribeAssetPropertyResponse = DescribeAssetPropertyResponse'
  { -- | The asset property\'s definition, alias, and notification state.
    --
    -- This response includes this object for normal asset properties. If you
    -- describe an asset property in a composite model, this response includes
    -- the asset property information in @compositeModel@.
    DescribeAssetPropertyResponse -> Maybe Property
assetProperty :: Prelude.Maybe Property,
    -- | The composite asset model that declares this asset property, if this
    -- asset property exists in a composite model.
    DescribeAssetPropertyResponse -> Maybe CompositeModelProperty
compositeModel :: Prelude.Maybe CompositeModelProperty,
    -- | The response's http status code.
    DescribeAssetPropertyResponse -> Int
httpStatus :: Prelude.Int,
    -- | The ID of the asset.
    DescribeAssetPropertyResponse -> Text
assetId :: Prelude.Text,
    -- | The name of the asset.
    DescribeAssetPropertyResponse -> Text
assetName :: Prelude.Text,
    -- | The ID of the asset model.
    DescribeAssetPropertyResponse -> Text
assetModelId :: Prelude.Text
  }
  deriving (DescribeAssetPropertyResponse
-> DescribeAssetPropertyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeAssetPropertyResponse
-> DescribeAssetPropertyResponse -> Bool
$c/= :: DescribeAssetPropertyResponse
-> DescribeAssetPropertyResponse -> Bool
== :: DescribeAssetPropertyResponse
-> DescribeAssetPropertyResponse -> Bool
$c== :: DescribeAssetPropertyResponse
-> DescribeAssetPropertyResponse -> Bool
Prelude.Eq, ReadPrec [DescribeAssetPropertyResponse]
ReadPrec DescribeAssetPropertyResponse
Int -> ReadS DescribeAssetPropertyResponse
ReadS [DescribeAssetPropertyResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeAssetPropertyResponse]
$creadListPrec :: ReadPrec [DescribeAssetPropertyResponse]
readPrec :: ReadPrec DescribeAssetPropertyResponse
$creadPrec :: ReadPrec DescribeAssetPropertyResponse
readList :: ReadS [DescribeAssetPropertyResponse]
$creadList :: ReadS [DescribeAssetPropertyResponse]
readsPrec :: Int -> ReadS DescribeAssetPropertyResponse
$creadsPrec :: Int -> ReadS DescribeAssetPropertyResponse
Prelude.Read, Int -> DescribeAssetPropertyResponse -> ShowS
[DescribeAssetPropertyResponse] -> ShowS
DescribeAssetPropertyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeAssetPropertyResponse] -> ShowS
$cshowList :: [DescribeAssetPropertyResponse] -> ShowS
show :: DescribeAssetPropertyResponse -> String
$cshow :: DescribeAssetPropertyResponse -> String
showsPrec :: Int -> DescribeAssetPropertyResponse -> ShowS
$cshowsPrec :: Int -> DescribeAssetPropertyResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeAssetPropertyResponse x
-> DescribeAssetPropertyResponse
forall x.
DescribeAssetPropertyResponse
-> Rep DescribeAssetPropertyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeAssetPropertyResponse x
-> DescribeAssetPropertyResponse
$cfrom :: forall x.
DescribeAssetPropertyResponse
-> Rep DescribeAssetPropertyResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeAssetPropertyResponse' 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:
--
-- 'assetProperty', 'describeAssetPropertyResponse_assetProperty' - The asset property\'s definition, alias, and notification state.
--
-- This response includes this object for normal asset properties. If you
-- describe an asset property in a composite model, this response includes
-- the asset property information in @compositeModel@.
--
-- 'compositeModel', 'describeAssetPropertyResponse_compositeModel' - The composite asset model that declares this asset property, if this
-- asset property exists in a composite model.
--
-- 'httpStatus', 'describeAssetPropertyResponse_httpStatus' - The response's http status code.
--
-- 'assetId', 'describeAssetPropertyResponse_assetId' - The ID of the asset.
--
-- 'assetName', 'describeAssetPropertyResponse_assetName' - The name of the asset.
--
-- 'assetModelId', 'describeAssetPropertyResponse_assetModelId' - The ID of the asset model.
newDescribeAssetPropertyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'assetId'
  Prelude.Text ->
  -- | 'assetName'
  Prelude.Text ->
  -- | 'assetModelId'
  Prelude.Text ->
  DescribeAssetPropertyResponse
newDescribeAssetPropertyResponse :: Int -> Text -> Text -> Text -> DescribeAssetPropertyResponse
newDescribeAssetPropertyResponse
  Int
pHttpStatus_
  Text
pAssetId_
  Text
pAssetName_
  Text
pAssetModelId_ =
    DescribeAssetPropertyResponse'
      { $sel:assetProperty:DescribeAssetPropertyResponse' :: Maybe Property
assetProperty =
          forall a. Maybe a
Prelude.Nothing,
        $sel:compositeModel:DescribeAssetPropertyResponse' :: Maybe CompositeModelProperty
compositeModel = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeAssetPropertyResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:assetId:DescribeAssetPropertyResponse' :: Text
assetId = Text
pAssetId_,
        $sel:assetName:DescribeAssetPropertyResponse' :: Text
assetName = Text
pAssetName_,
        $sel:assetModelId:DescribeAssetPropertyResponse' :: Text
assetModelId = Text
pAssetModelId_
      }

-- | The asset property\'s definition, alias, and notification state.
--
-- This response includes this object for normal asset properties. If you
-- describe an asset property in a composite model, this response includes
-- the asset property information in @compositeModel@.
describeAssetPropertyResponse_assetProperty :: Lens.Lens' DescribeAssetPropertyResponse (Prelude.Maybe Property)
describeAssetPropertyResponse_assetProperty :: Lens' DescribeAssetPropertyResponse (Maybe Property)
describeAssetPropertyResponse_assetProperty = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAssetPropertyResponse' {Maybe Property
assetProperty :: Maybe Property
$sel:assetProperty:DescribeAssetPropertyResponse' :: DescribeAssetPropertyResponse -> Maybe Property
assetProperty} -> Maybe Property
assetProperty) (\s :: DescribeAssetPropertyResponse
s@DescribeAssetPropertyResponse' {} Maybe Property
a -> DescribeAssetPropertyResponse
s {$sel:assetProperty:DescribeAssetPropertyResponse' :: Maybe Property
assetProperty = Maybe Property
a} :: DescribeAssetPropertyResponse)

-- | The composite asset model that declares this asset property, if this
-- asset property exists in a composite model.
describeAssetPropertyResponse_compositeModel :: Lens.Lens' DescribeAssetPropertyResponse (Prelude.Maybe CompositeModelProperty)
describeAssetPropertyResponse_compositeModel :: Lens' DescribeAssetPropertyResponse (Maybe CompositeModelProperty)
describeAssetPropertyResponse_compositeModel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAssetPropertyResponse' {Maybe CompositeModelProperty
compositeModel :: Maybe CompositeModelProperty
$sel:compositeModel:DescribeAssetPropertyResponse' :: DescribeAssetPropertyResponse -> Maybe CompositeModelProperty
compositeModel} -> Maybe CompositeModelProperty
compositeModel) (\s :: DescribeAssetPropertyResponse
s@DescribeAssetPropertyResponse' {} Maybe CompositeModelProperty
a -> DescribeAssetPropertyResponse
s {$sel:compositeModel:DescribeAssetPropertyResponse' :: Maybe CompositeModelProperty
compositeModel = Maybe CompositeModelProperty
a} :: DescribeAssetPropertyResponse)

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

-- | The ID of the asset.
describeAssetPropertyResponse_assetId :: Lens.Lens' DescribeAssetPropertyResponse Prelude.Text
describeAssetPropertyResponse_assetId :: Lens' DescribeAssetPropertyResponse Text
describeAssetPropertyResponse_assetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAssetPropertyResponse' {Text
assetId :: Text
$sel:assetId:DescribeAssetPropertyResponse' :: DescribeAssetPropertyResponse -> Text
assetId} -> Text
assetId) (\s :: DescribeAssetPropertyResponse
s@DescribeAssetPropertyResponse' {} Text
a -> DescribeAssetPropertyResponse
s {$sel:assetId:DescribeAssetPropertyResponse' :: Text
assetId = Text
a} :: DescribeAssetPropertyResponse)

-- | The name of the asset.
describeAssetPropertyResponse_assetName :: Lens.Lens' DescribeAssetPropertyResponse Prelude.Text
describeAssetPropertyResponse_assetName :: Lens' DescribeAssetPropertyResponse Text
describeAssetPropertyResponse_assetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAssetPropertyResponse' {Text
assetName :: Text
$sel:assetName:DescribeAssetPropertyResponse' :: DescribeAssetPropertyResponse -> Text
assetName} -> Text
assetName) (\s :: DescribeAssetPropertyResponse
s@DescribeAssetPropertyResponse' {} Text
a -> DescribeAssetPropertyResponse
s {$sel:assetName:DescribeAssetPropertyResponse' :: Text
assetName = Text
a} :: DescribeAssetPropertyResponse)

-- | The ID of the asset model.
describeAssetPropertyResponse_assetModelId :: Lens.Lens' DescribeAssetPropertyResponse Prelude.Text
describeAssetPropertyResponse_assetModelId :: Lens' DescribeAssetPropertyResponse Text
describeAssetPropertyResponse_assetModelId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAssetPropertyResponse' {Text
assetModelId :: Text
$sel:assetModelId:DescribeAssetPropertyResponse' :: DescribeAssetPropertyResponse -> Text
assetModelId} -> Text
assetModelId) (\s :: DescribeAssetPropertyResponse
s@DescribeAssetPropertyResponse' {} Text
a -> DescribeAssetPropertyResponse
s {$sel:assetModelId:DescribeAssetPropertyResponse' :: Text
assetModelId = Text
a} :: DescribeAssetPropertyResponse)

instance Prelude.NFData DescribeAssetPropertyResponse where
  rnf :: DescribeAssetPropertyResponse -> ()
rnf DescribeAssetPropertyResponse' {Int
Maybe Property
Maybe CompositeModelProperty
Text
assetModelId :: Text
assetName :: Text
assetId :: Text
httpStatus :: Int
compositeModel :: Maybe CompositeModelProperty
assetProperty :: Maybe Property
$sel:assetModelId:DescribeAssetPropertyResponse' :: DescribeAssetPropertyResponse -> Text
$sel:assetName:DescribeAssetPropertyResponse' :: DescribeAssetPropertyResponse -> Text
$sel:assetId:DescribeAssetPropertyResponse' :: DescribeAssetPropertyResponse -> Text
$sel:httpStatus:DescribeAssetPropertyResponse' :: DescribeAssetPropertyResponse -> Int
$sel:compositeModel:DescribeAssetPropertyResponse' :: DescribeAssetPropertyResponse -> Maybe CompositeModelProperty
$sel:assetProperty:DescribeAssetPropertyResponse' :: DescribeAssetPropertyResponse -> Maybe Property
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Property
assetProperty
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CompositeModelProperty
compositeModel
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
assetId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
assetName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
assetModelId