{-# 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.SageMaker.DescribeFeatureMetadata
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Shows the metadata for a feature within a feature group.
module Amazonka.SageMaker.DescribeFeatureMetadata
  ( -- * Creating a Request
    DescribeFeatureMetadata (..),
    newDescribeFeatureMetadata,

    -- * Request Lenses
    describeFeatureMetadata_featureGroupName,
    describeFeatureMetadata_featureName,

    -- * Destructuring the Response
    DescribeFeatureMetadataResponse (..),
    newDescribeFeatureMetadataResponse,

    -- * Response Lenses
    describeFeatureMetadataResponse_description,
    describeFeatureMetadataResponse_parameters,
    describeFeatureMetadataResponse_httpStatus,
    describeFeatureMetadataResponse_featureGroupArn,
    describeFeatureMetadataResponse_featureGroupName,
    describeFeatureMetadataResponse_featureName,
    describeFeatureMetadataResponse_featureType,
    describeFeatureMetadataResponse_creationTime,
    describeFeatureMetadataResponse_lastModifiedTime,
  )
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.SageMaker.Types

-- | /See:/ 'newDescribeFeatureMetadata' smart constructor.
data DescribeFeatureMetadata = DescribeFeatureMetadata'
  { -- | The name of the feature group containing the feature.
    DescribeFeatureMetadata -> Text
featureGroupName :: Prelude.Text,
    -- | The name of the feature.
    DescribeFeatureMetadata -> Text
featureName :: Prelude.Text
  }
  deriving (DescribeFeatureMetadata -> DescribeFeatureMetadata -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeFeatureMetadata -> DescribeFeatureMetadata -> Bool
$c/= :: DescribeFeatureMetadata -> DescribeFeatureMetadata -> Bool
== :: DescribeFeatureMetadata -> DescribeFeatureMetadata -> Bool
$c== :: DescribeFeatureMetadata -> DescribeFeatureMetadata -> Bool
Prelude.Eq, ReadPrec [DescribeFeatureMetadata]
ReadPrec DescribeFeatureMetadata
Int -> ReadS DescribeFeatureMetadata
ReadS [DescribeFeatureMetadata]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeFeatureMetadata]
$creadListPrec :: ReadPrec [DescribeFeatureMetadata]
readPrec :: ReadPrec DescribeFeatureMetadata
$creadPrec :: ReadPrec DescribeFeatureMetadata
readList :: ReadS [DescribeFeatureMetadata]
$creadList :: ReadS [DescribeFeatureMetadata]
readsPrec :: Int -> ReadS DescribeFeatureMetadata
$creadsPrec :: Int -> ReadS DescribeFeatureMetadata
Prelude.Read, Int -> DescribeFeatureMetadata -> ShowS
[DescribeFeatureMetadata] -> ShowS
DescribeFeatureMetadata -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeFeatureMetadata] -> ShowS
$cshowList :: [DescribeFeatureMetadata] -> ShowS
show :: DescribeFeatureMetadata -> String
$cshow :: DescribeFeatureMetadata -> String
showsPrec :: Int -> DescribeFeatureMetadata -> ShowS
$cshowsPrec :: Int -> DescribeFeatureMetadata -> ShowS
Prelude.Show, forall x. Rep DescribeFeatureMetadata x -> DescribeFeatureMetadata
forall x. DescribeFeatureMetadata -> Rep DescribeFeatureMetadata x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeFeatureMetadata x -> DescribeFeatureMetadata
$cfrom :: forall x. DescribeFeatureMetadata -> Rep DescribeFeatureMetadata x
Prelude.Generic)

-- |
-- Create a value of 'DescribeFeatureMetadata' 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:
--
-- 'featureGroupName', 'describeFeatureMetadata_featureGroupName' - The name of the feature group containing the feature.
--
-- 'featureName', 'describeFeatureMetadata_featureName' - The name of the feature.
newDescribeFeatureMetadata ::
  -- | 'featureGroupName'
  Prelude.Text ->
  -- | 'featureName'
  Prelude.Text ->
  DescribeFeatureMetadata
newDescribeFeatureMetadata :: Text -> Text -> DescribeFeatureMetadata
newDescribeFeatureMetadata
  Text
pFeatureGroupName_
  Text
pFeatureName_ =
    DescribeFeatureMetadata'
      { $sel:featureGroupName:DescribeFeatureMetadata' :: Text
featureGroupName =
          Text
pFeatureGroupName_,
        $sel:featureName:DescribeFeatureMetadata' :: Text
featureName = Text
pFeatureName_
      }

-- | The name of the feature group containing the feature.
describeFeatureMetadata_featureGroupName :: Lens.Lens' DescribeFeatureMetadata Prelude.Text
describeFeatureMetadata_featureGroupName :: Lens' DescribeFeatureMetadata Text
describeFeatureMetadata_featureGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureMetadata' {Text
featureGroupName :: Text
$sel:featureGroupName:DescribeFeatureMetadata' :: DescribeFeatureMetadata -> Text
featureGroupName} -> Text
featureGroupName) (\s :: DescribeFeatureMetadata
s@DescribeFeatureMetadata' {} Text
a -> DescribeFeatureMetadata
s {$sel:featureGroupName:DescribeFeatureMetadata' :: Text
featureGroupName = Text
a} :: DescribeFeatureMetadata)

-- | The name of the feature.
describeFeatureMetadata_featureName :: Lens.Lens' DescribeFeatureMetadata Prelude.Text
describeFeatureMetadata_featureName :: Lens' DescribeFeatureMetadata Text
describeFeatureMetadata_featureName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureMetadata' {Text
featureName :: Text
$sel:featureName:DescribeFeatureMetadata' :: DescribeFeatureMetadata -> Text
featureName} -> Text
featureName) (\s :: DescribeFeatureMetadata
s@DescribeFeatureMetadata' {} Text
a -> DescribeFeatureMetadata
s {$sel:featureName:DescribeFeatureMetadata' :: Text
featureName = Text
a} :: DescribeFeatureMetadata)

instance Core.AWSRequest DescribeFeatureMetadata where
  type
    AWSResponse DescribeFeatureMetadata =
      DescribeFeatureMetadataResponse
  request :: (Service -> Service)
-> DescribeFeatureMetadata -> Request DescribeFeatureMetadata
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 DescribeFeatureMetadata
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeFeatureMetadata)))
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 [FeatureParameter]
-> Int
-> Text
-> Text
-> Text
-> FeatureType
-> POSIX
-> POSIX
-> DescribeFeatureMetadataResponse
DescribeFeatureMetadataResponse'
            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
"Description")
            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
"Parameters" 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.<*> (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
"FeatureGroupArn")
            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
"FeatureGroupName")
            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
"FeatureName")
            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
"FeatureType")
            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
"CreationTime")
            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
"LastModifiedTime")
      )

instance Prelude.Hashable DescribeFeatureMetadata where
  hashWithSalt :: Int -> DescribeFeatureMetadata -> Int
hashWithSalt Int
_salt DescribeFeatureMetadata' {Text
featureName :: Text
featureGroupName :: Text
$sel:featureName:DescribeFeatureMetadata' :: DescribeFeatureMetadata -> Text
$sel:featureGroupName:DescribeFeatureMetadata' :: DescribeFeatureMetadata -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
featureGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
featureName

instance Prelude.NFData DescribeFeatureMetadata where
  rnf :: DescribeFeatureMetadata -> ()
rnf DescribeFeatureMetadata' {Text
featureName :: Text
featureGroupName :: Text
$sel:featureName:DescribeFeatureMetadata' :: DescribeFeatureMetadata -> Text
$sel:featureGroupName:DescribeFeatureMetadata' :: DescribeFeatureMetadata -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
featureGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
featureName

instance Data.ToHeaders DescribeFeatureMetadata where
  toHeaders :: DescribeFeatureMetadata -> 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
"SageMaker.DescribeFeatureMetadata" ::
                          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 DescribeFeatureMetadata where
  toJSON :: DescribeFeatureMetadata -> Value
toJSON DescribeFeatureMetadata' {Text
featureName :: Text
featureGroupName :: Text
$sel:featureName:DescribeFeatureMetadata' :: DescribeFeatureMetadata -> Text
$sel:featureGroupName:DescribeFeatureMetadata' :: DescribeFeatureMetadata -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"FeatureGroupName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
featureGroupName),
            forall a. a -> Maybe a
Prelude.Just (Key
"FeatureName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
featureName)
          ]
      )

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

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

-- | /See:/ 'newDescribeFeatureMetadataResponse' smart constructor.
data DescribeFeatureMetadataResponse = DescribeFeatureMetadataResponse'
  { -- | The description you added to describe the feature.
    DescribeFeatureMetadataResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The key-value pairs that you added to describe the feature.
    DescribeFeatureMetadataResponse -> Maybe [FeatureParameter]
parameters :: Prelude.Maybe [FeatureParameter],
    -- | The response's http status code.
    DescribeFeatureMetadataResponse -> Int
httpStatus :: Prelude.Int,
    -- | The Amazon Resource Number (ARN) of the feature group that contains the
    -- feature.
    DescribeFeatureMetadataResponse -> Text
featureGroupArn :: Prelude.Text,
    -- | The name of the feature group that you\'ve specified.
    DescribeFeatureMetadataResponse -> Text
featureGroupName :: Prelude.Text,
    -- | The name of the feature that you\'ve specified.
    DescribeFeatureMetadataResponse -> Text
featureName :: Prelude.Text,
    -- | The data type of the feature.
    DescribeFeatureMetadataResponse -> FeatureType
featureType :: FeatureType,
    -- | A timestamp indicating when the feature was created.
    DescribeFeatureMetadataResponse -> POSIX
creationTime :: Data.POSIX,
    -- | A timestamp indicating when the metadata for the feature group was
    -- modified. For example, if you add a parameter describing the feature,
    -- the timestamp changes to reflect the last time you
    DescribeFeatureMetadataResponse -> POSIX
lastModifiedTime :: Data.POSIX
  }
  deriving (DescribeFeatureMetadataResponse
-> DescribeFeatureMetadataResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeFeatureMetadataResponse
-> DescribeFeatureMetadataResponse -> Bool
$c/= :: DescribeFeatureMetadataResponse
-> DescribeFeatureMetadataResponse -> Bool
== :: DescribeFeatureMetadataResponse
-> DescribeFeatureMetadataResponse -> Bool
$c== :: DescribeFeatureMetadataResponse
-> DescribeFeatureMetadataResponse -> Bool
Prelude.Eq, ReadPrec [DescribeFeatureMetadataResponse]
ReadPrec DescribeFeatureMetadataResponse
Int -> ReadS DescribeFeatureMetadataResponse
ReadS [DescribeFeatureMetadataResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeFeatureMetadataResponse]
$creadListPrec :: ReadPrec [DescribeFeatureMetadataResponse]
readPrec :: ReadPrec DescribeFeatureMetadataResponse
$creadPrec :: ReadPrec DescribeFeatureMetadataResponse
readList :: ReadS [DescribeFeatureMetadataResponse]
$creadList :: ReadS [DescribeFeatureMetadataResponse]
readsPrec :: Int -> ReadS DescribeFeatureMetadataResponse
$creadsPrec :: Int -> ReadS DescribeFeatureMetadataResponse
Prelude.Read, Int -> DescribeFeatureMetadataResponse -> ShowS
[DescribeFeatureMetadataResponse] -> ShowS
DescribeFeatureMetadataResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeFeatureMetadataResponse] -> ShowS
$cshowList :: [DescribeFeatureMetadataResponse] -> ShowS
show :: DescribeFeatureMetadataResponse -> String
$cshow :: DescribeFeatureMetadataResponse -> String
showsPrec :: Int -> DescribeFeatureMetadataResponse -> ShowS
$cshowsPrec :: Int -> DescribeFeatureMetadataResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeFeatureMetadataResponse x
-> DescribeFeatureMetadataResponse
forall x.
DescribeFeatureMetadataResponse
-> Rep DescribeFeatureMetadataResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeFeatureMetadataResponse x
-> DescribeFeatureMetadataResponse
$cfrom :: forall x.
DescribeFeatureMetadataResponse
-> Rep DescribeFeatureMetadataResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeFeatureMetadataResponse' 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:
--
-- 'description', 'describeFeatureMetadataResponse_description' - The description you added to describe the feature.
--
-- 'parameters', 'describeFeatureMetadataResponse_parameters' - The key-value pairs that you added to describe the feature.
--
-- 'httpStatus', 'describeFeatureMetadataResponse_httpStatus' - The response's http status code.
--
-- 'featureGroupArn', 'describeFeatureMetadataResponse_featureGroupArn' - The Amazon Resource Number (ARN) of the feature group that contains the
-- feature.
--
-- 'featureGroupName', 'describeFeatureMetadataResponse_featureGroupName' - The name of the feature group that you\'ve specified.
--
-- 'featureName', 'describeFeatureMetadataResponse_featureName' - The name of the feature that you\'ve specified.
--
-- 'featureType', 'describeFeatureMetadataResponse_featureType' - The data type of the feature.
--
-- 'creationTime', 'describeFeatureMetadataResponse_creationTime' - A timestamp indicating when the feature was created.
--
-- 'lastModifiedTime', 'describeFeatureMetadataResponse_lastModifiedTime' - A timestamp indicating when the metadata for the feature group was
-- modified. For example, if you add a parameter describing the feature,
-- the timestamp changes to reflect the last time you
newDescribeFeatureMetadataResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'featureGroupArn'
  Prelude.Text ->
  -- | 'featureGroupName'
  Prelude.Text ->
  -- | 'featureName'
  Prelude.Text ->
  -- | 'featureType'
  FeatureType ->
  -- | 'creationTime'
  Prelude.UTCTime ->
  -- | 'lastModifiedTime'
  Prelude.UTCTime ->
  DescribeFeatureMetadataResponse
newDescribeFeatureMetadataResponse :: Int
-> Text
-> Text
-> Text
-> FeatureType
-> UTCTime
-> UTCTime
-> DescribeFeatureMetadataResponse
newDescribeFeatureMetadataResponse
  Int
pHttpStatus_
  Text
pFeatureGroupArn_
  Text
pFeatureGroupName_
  Text
pFeatureName_
  FeatureType
pFeatureType_
  UTCTime
pCreationTime_
  UTCTime
pLastModifiedTime_ =
    DescribeFeatureMetadataResponse'
      { $sel:description:DescribeFeatureMetadataResponse' :: Maybe Text
description =
          forall a. Maybe a
Prelude.Nothing,
        $sel:parameters:DescribeFeatureMetadataResponse' :: Maybe [FeatureParameter]
parameters = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeFeatureMetadataResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:featureGroupArn:DescribeFeatureMetadataResponse' :: Text
featureGroupArn = Text
pFeatureGroupArn_,
        $sel:featureGroupName:DescribeFeatureMetadataResponse' :: Text
featureGroupName = Text
pFeatureGroupName_,
        $sel:featureName:DescribeFeatureMetadataResponse' :: Text
featureName = Text
pFeatureName_,
        $sel:featureType:DescribeFeatureMetadataResponse' :: FeatureType
featureType = FeatureType
pFeatureType_,
        $sel:creationTime:DescribeFeatureMetadataResponse' :: POSIX
creationTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreationTime_,
        $sel:lastModifiedTime:DescribeFeatureMetadataResponse' :: POSIX
lastModifiedTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pLastModifiedTime_
      }

-- | The description you added to describe the feature.
describeFeatureMetadataResponse_description :: Lens.Lens' DescribeFeatureMetadataResponse (Prelude.Maybe Prelude.Text)
describeFeatureMetadataResponse_description :: Lens' DescribeFeatureMetadataResponse (Maybe Text)
describeFeatureMetadataResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureMetadataResponse' {Maybe Text
description :: Maybe Text
$sel:description:DescribeFeatureMetadataResponse' :: DescribeFeatureMetadataResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: DescribeFeatureMetadataResponse
s@DescribeFeatureMetadataResponse' {} Maybe Text
a -> DescribeFeatureMetadataResponse
s {$sel:description:DescribeFeatureMetadataResponse' :: Maybe Text
description = Maybe Text
a} :: DescribeFeatureMetadataResponse)

-- | The key-value pairs that you added to describe the feature.
describeFeatureMetadataResponse_parameters :: Lens.Lens' DescribeFeatureMetadataResponse (Prelude.Maybe [FeatureParameter])
describeFeatureMetadataResponse_parameters :: Lens' DescribeFeatureMetadataResponse (Maybe [FeatureParameter])
describeFeatureMetadataResponse_parameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureMetadataResponse' {Maybe [FeatureParameter]
parameters :: Maybe [FeatureParameter]
$sel:parameters:DescribeFeatureMetadataResponse' :: DescribeFeatureMetadataResponse -> Maybe [FeatureParameter]
parameters} -> Maybe [FeatureParameter]
parameters) (\s :: DescribeFeatureMetadataResponse
s@DescribeFeatureMetadataResponse' {} Maybe [FeatureParameter]
a -> DescribeFeatureMetadataResponse
s {$sel:parameters:DescribeFeatureMetadataResponse' :: Maybe [FeatureParameter]
parameters = Maybe [FeatureParameter]
a} :: DescribeFeatureMetadataResponse) 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 response's http status code.
describeFeatureMetadataResponse_httpStatus :: Lens.Lens' DescribeFeatureMetadataResponse Prelude.Int
describeFeatureMetadataResponse_httpStatus :: Lens' DescribeFeatureMetadataResponse Int
describeFeatureMetadataResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureMetadataResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeFeatureMetadataResponse' :: DescribeFeatureMetadataResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeFeatureMetadataResponse
s@DescribeFeatureMetadataResponse' {} Int
a -> DescribeFeatureMetadataResponse
s {$sel:httpStatus:DescribeFeatureMetadataResponse' :: Int
httpStatus = Int
a} :: DescribeFeatureMetadataResponse)

-- | The Amazon Resource Number (ARN) of the feature group that contains the
-- feature.
describeFeatureMetadataResponse_featureGroupArn :: Lens.Lens' DescribeFeatureMetadataResponse Prelude.Text
describeFeatureMetadataResponse_featureGroupArn :: Lens' DescribeFeatureMetadataResponse Text
describeFeatureMetadataResponse_featureGroupArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureMetadataResponse' {Text
featureGroupArn :: Text
$sel:featureGroupArn:DescribeFeatureMetadataResponse' :: DescribeFeatureMetadataResponse -> Text
featureGroupArn} -> Text
featureGroupArn) (\s :: DescribeFeatureMetadataResponse
s@DescribeFeatureMetadataResponse' {} Text
a -> DescribeFeatureMetadataResponse
s {$sel:featureGroupArn:DescribeFeatureMetadataResponse' :: Text
featureGroupArn = Text
a} :: DescribeFeatureMetadataResponse)

-- | The name of the feature group that you\'ve specified.
describeFeatureMetadataResponse_featureGroupName :: Lens.Lens' DescribeFeatureMetadataResponse Prelude.Text
describeFeatureMetadataResponse_featureGroupName :: Lens' DescribeFeatureMetadataResponse Text
describeFeatureMetadataResponse_featureGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureMetadataResponse' {Text
featureGroupName :: Text
$sel:featureGroupName:DescribeFeatureMetadataResponse' :: DescribeFeatureMetadataResponse -> Text
featureGroupName} -> Text
featureGroupName) (\s :: DescribeFeatureMetadataResponse
s@DescribeFeatureMetadataResponse' {} Text
a -> DescribeFeatureMetadataResponse
s {$sel:featureGroupName:DescribeFeatureMetadataResponse' :: Text
featureGroupName = Text
a} :: DescribeFeatureMetadataResponse)

-- | The name of the feature that you\'ve specified.
describeFeatureMetadataResponse_featureName :: Lens.Lens' DescribeFeatureMetadataResponse Prelude.Text
describeFeatureMetadataResponse_featureName :: Lens' DescribeFeatureMetadataResponse Text
describeFeatureMetadataResponse_featureName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureMetadataResponse' {Text
featureName :: Text
$sel:featureName:DescribeFeatureMetadataResponse' :: DescribeFeatureMetadataResponse -> Text
featureName} -> Text
featureName) (\s :: DescribeFeatureMetadataResponse
s@DescribeFeatureMetadataResponse' {} Text
a -> DescribeFeatureMetadataResponse
s {$sel:featureName:DescribeFeatureMetadataResponse' :: Text
featureName = Text
a} :: DescribeFeatureMetadataResponse)

-- | The data type of the feature.
describeFeatureMetadataResponse_featureType :: Lens.Lens' DescribeFeatureMetadataResponse FeatureType
describeFeatureMetadataResponse_featureType :: Lens' DescribeFeatureMetadataResponse FeatureType
describeFeatureMetadataResponse_featureType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureMetadataResponse' {FeatureType
featureType :: FeatureType
$sel:featureType:DescribeFeatureMetadataResponse' :: DescribeFeatureMetadataResponse -> FeatureType
featureType} -> FeatureType
featureType) (\s :: DescribeFeatureMetadataResponse
s@DescribeFeatureMetadataResponse' {} FeatureType
a -> DescribeFeatureMetadataResponse
s {$sel:featureType:DescribeFeatureMetadataResponse' :: FeatureType
featureType = FeatureType
a} :: DescribeFeatureMetadataResponse)

-- | A timestamp indicating when the feature was created.
describeFeatureMetadataResponse_creationTime :: Lens.Lens' DescribeFeatureMetadataResponse Prelude.UTCTime
describeFeatureMetadataResponse_creationTime :: Lens' DescribeFeatureMetadataResponse UTCTime
describeFeatureMetadataResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureMetadataResponse' {POSIX
creationTime :: POSIX
$sel:creationTime:DescribeFeatureMetadataResponse' :: DescribeFeatureMetadataResponse -> POSIX
creationTime} -> POSIX
creationTime) (\s :: DescribeFeatureMetadataResponse
s@DescribeFeatureMetadataResponse' {} POSIX
a -> DescribeFeatureMetadataResponse
s {$sel:creationTime:DescribeFeatureMetadataResponse' :: POSIX
creationTime = POSIX
a} :: DescribeFeatureMetadataResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | A timestamp indicating when the metadata for the feature group was
-- modified. For example, if you add a parameter describing the feature,
-- the timestamp changes to reflect the last time you
describeFeatureMetadataResponse_lastModifiedTime :: Lens.Lens' DescribeFeatureMetadataResponse Prelude.UTCTime
describeFeatureMetadataResponse_lastModifiedTime :: Lens' DescribeFeatureMetadataResponse UTCTime
describeFeatureMetadataResponse_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureMetadataResponse' {POSIX
lastModifiedTime :: POSIX
$sel:lastModifiedTime:DescribeFeatureMetadataResponse' :: DescribeFeatureMetadataResponse -> POSIX
lastModifiedTime} -> POSIX
lastModifiedTime) (\s :: DescribeFeatureMetadataResponse
s@DescribeFeatureMetadataResponse' {} POSIX
a -> DescribeFeatureMetadataResponse
s {$sel:lastModifiedTime:DescribeFeatureMetadataResponse' :: POSIX
lastModifiedTime = POSIX
a} :: DescribeFeatureMetadataResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

instance
  Prelude.NFData
    DescribeFeatureMetadataResponse
  where
  rnf :: DescribeFeatureMetadataResponse -> ()
rnf DescribeFeatureMetadataResponse' {Int
Maybe [FeatureParameter]
Maybe Text
Text
POSIX
FeatureType
lastModifiedTime :: POSIX
creationTime :: POSIX
featureType :: FeatureType
featureName :: Text
featureGroupName :: Text
featureGroupArn :: Text
httpStatus :: Int
parameters :: Maybe [FeatureParameter]
description :: Maybe Text
$sel:lastModifiedTime:DescribeFeatureMetadataResponse' :: DescribeFeatureMetadataResponse -> POSIX
$sel:creationTime:DescribeFeatureMetadataResponse' :: DescribeFeatureMetadataResponse -> POSIX
$sel:featureType:DescribeFeatureMetadataResponse' :: DescribeFeatureMetadataResponse -> FeatureType
$sel:featureName:DescribeFeatureMetadataResponse' :: DescribeFeatureMetadataResponse -> Text
$sel:featureGroupName:DescribeFeatureMetadataResponse' :: DescribeFeatureMetadataResponse -> Text
$sel:featureGroupArn:DescribeFeatureMetadataResponse' :: DescribeFeatureMetadataResponse -> Text
$sel:httpStatus:DescribeFeatureMetadataResponse' :: DescribeFeatureMetadataResponse -> Int
$sel:parameters:DescribeFeatureMetadataResponse' :: DescribeFeatureMetadataResponse -> Maybe [FeatureParameter]
$sel:description:DescribeFeatureMetadataResponse' :: DescribeFeatureMetadataResponse -> Maybe Text
..} =
    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 [FeatureParameter]
parameters
      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
featureGroupArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
featureGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
featureName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf FeatureType
featureType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
lastModifiedTime