{-# 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.UpdateFeatureMetadata
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates the description and parameters of the feature group.
module Amazonka.SageMaker.UpdateFeatureMetadata
  ( -- * Creating a Request
    UpdateFeatureMetadata (..),
    newUpdateFeatureMetadata,

    -- * Request Lenses
    updateFeatureMetadata_description,
    updateFeatureMetadata_parameterAdditions,
    updateFeatureMetadata_parameterRemovals,
    updateFeatureMetadata_featureGroupName,
    updateFeatureMetadata_featureName,

    -- * Destructuring the Response
    UpdateFeatureMetadataResponse (..),
    newUpdateFeatureMetadataResponse,
  )
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:/ 'newUpdateFeatureMetadata' smart constructor.
data UpdateFeatureMetadata = UpdateFeatureMetadata'
  { -- | A description that you can write to better describe the feature.
    UpdateFeatureMetadata -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | A list of key-value pairs that you can add to better describe the
    -- feature.
    UpdateFeatureMetadata -> Maybe [FeatureParameter]
parameterAdditions :: Prelude.Maybe [FeatureParameter],
    -- | A list of parameter keys that you can specify to remove parameters that
    -- describe your feature.
    UpdateFeatureMetadata -> Maybe [Text]
parameterRemovals :: Prelude.Maybe [Prelude.Text],
    -- | The name of the feature group containing the feature that you\'re
    -- updating.
    UpdateFeatureMetadata -> Text
featureGroupName :: Prelude.Text,
    -- | The name of the feature that you\'re updating.
    UpdateFeatureMetadata -> Text
featureName :: Prelude.Text
  }
  deriving (UpdateFeatureMetadata -> UpdateFeatureMetadata -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateFeatureMetadata -> UpdateFeatureMetadata -> Bool
$c/= :: UpdateFeatureMetadata -> UpdateFeatureMetadata -> Bool
== :: UpdateFeatureMetadata -> UpdateFeatureMetadata -> Bool
$c== :: UpdateFeatureMetadata -> UpdateFeatureMetadata -> Bool
Prelude.Eq, ReadPrec [UpdateFeatureMetadata]
ReadPrec UpdateFeatureMetadata
Int -> ReadS UpdateFeatureMetadata
ReadS [UpdateFeatureMetadata]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateFeatureMetadata]
$creadListPrec :: ReadPrec [UpdateFeatureMetadata]
readPrec :: ReadPrec UpdateFeatureMetadata
$creadPrec :: ReadPrec UpdateFeatureMetadata
readList :: ReadS [UpdateFeatureMetadata]
$creadList :: ReadS [UpdateFeatureMetadata]
readsPrec :: Int -> ReadS UpdateFeatureMetadata
$creadsPrec :: Int -> ReadS UpdateFeatureMetadata
Prelude.Read, Int -> UpdateFeatureMetadata -> ShowS
[UpdateFeatureMetadata] -> ShowS
UpdateFeatureMetadata -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateFeatureMetadata] -> ShowS
$cshowList :: [UpdateFeatureMetadata] -> ShowS
show :: UpdateFeatureMetadata -> String
$cshow :: UpdateFeatureMetadata -> String
showsPrec :: Int -> UpdateFeatureMetadata -> ShowS
$cshowsPrec :: Int -> UpdateFeatureMetadata -> ShowS
Prelude.Show, forall x. Rep UpdateFeatureMetadata x -> UpdateFeatureMetadata
forall x. UpdateFeatureMetadata -> Rep UpdateFeatureMetadata x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateFeatureMetadata x -> UpdateFeatureMetadata
$cfrom :: forall x. UpdateFeatureMetadata -> Rep UpdateFeatureMetadata x
Prelude.Generic)

-- |
-- Create a value of 'UpdateFeatureMetadata' 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', 'updateFeatureMetadata_description' - A description that you can write to better describe the feature.
--
-- 'parameterAdditions', 'updateFeatureMetadata_parameterAdditions' - A list of key-value pairs that you can add to better describe the
-- feature.
--
-- 'parameterRemovals', 'updateFeatureMetadata_parameterRemovals' - A list of parameter keys that you can specify to remove parameters that
-- describe your feature.
--
-- 'featureGroupName', 'updateFeatureMetadata_featureGroupName' - The name of the feature group containing the feature that you\'re
-- updating.
--
-- 'featureName', 'updateFeatureMetadata_featureName' - The name of the feature that you\'re updating.
newUpdateFeatureMetadata ::
  -- | 'featureGroupName'
  Prelude.Text ->
  -- | 'featureName'
  Prelude.Text ->
  UpdateFeatureMetadata
newUpdateFeatureMetadata :: Text -> Text -> UpdateFeatureMetadata
newUpdateFeatureMetadata
  Text
pFeatureGroupName_
  Text
pFeatureName_ =
    UpdateFeatureMetadata'
      { $sel:description:UpdateFeatureMetadata' :: Maybe Text
description =
          forall a. Maybe a
Prelude.Nothing,
        $sel:parameterAdditions:UpdateFeatureMetadata' :: Maybe [FeatureParameter]
parameterAdditions = forall a. Maybe a
Prelude.Nothing,
        $sel:parameterRemovals:UpdateFeatureMetadata' :: Maybe [Text]
parameterRemovals = forall a. Maybe a
Prelude.Nothing,
        $sel:featureGroupName:UpdateFeatureMetadata' :: Text
featureGroupName = Text
pFeatureGroupName_,
        $sel:featureName:UpdateFeatureMetadata' :: Text
featureName = Text
pFeatureName_
      }

-- | A description that you can write to better describe the feature.
updateFeatureMetadata_description :: Lens.Lens' UpdateFeatureMetadata (Prelude.Maybe Prelude.Text)
updateFeatureMetadata_description :: Lens' UpdateFeatureMetadata (Maybe Text)
updateFeatureMetadata_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFeatureMetadata' {Maybe Text
description :: Maybe Text
$sel:description:UpdateFeatureMetadata' :: UpdateFeatureMetadata -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateFeatureMetadata
s@UpdateFeatureMetadata' {} Maybe Text
a -> UpdateFeatureMetadata
s {$sel:description:UpdateFeatureMetadata' :: Maybe Text
description = Maybe Text
a} :: UpdateFeatureMetadata)

-- | A list of key-value pairs that you can add to better describe the
-- feature.
updateFeatureMetadata_parameterAdditions :: Lens.Lens' UpdateFeatureMetadata (Prelude.Maybe [FeatureParameter])
updateFeatureMetadata_parameterAdditions :: Lens' UpdateFeatureMetadata (Maybe [FeatureParameter])
updateFeatureMetadata_parameterAdditions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFeatureMetadata' {Maybe [FeatureParameter]
parameterAdditions :: Maybe [FeatureParameter]
$sel:parameterAdditions:UpdateFeatureMetadata' :: UpdateFeatureMetadata -> Maybe [FeatureParameter]
parameterAdditions} -> Maybe [FeatureParameter]
parameterAdditions) (\s :: UpdateFeatureMetadata
s@UpdateFeatureMetadata' {} Maybe [FeatureParameter]
a -> UpdateFeatureMetadata
s {$sel:parameterAdditions:UpdateFeatureMetadata' :: Maybe [FeatureParameter]
parameterAdditions = Maybe [FeatureParameter]
a} :: UpdateFeatureMetadata) 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

-- | A list of parameter keys that you can specify to remove parameters that
-- describe your feature.
updateFeatureMetadata_parameterRemovals :: Lens.Lens' UpdateFeatureMetadata (Prelude.Maybe [Prelude.Text])
updateFeatureMetadata_parameterRemovals :: Lens' UpdateFeatureMetadata (Maybe [Text])
updateFeatureMetadata_parameterRemovals = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFeatureMetadata' {Maybe [Text]
parameterRemovals :: Maybe [Text]
$sel:parameterRemovals:UpdateFeatureMetadata' :: UpdateFeatureMetadata -> Maybe [Text]
parameterRemovals} -> Maybe [Text]
parameterRemovals) (\s :: UpdateFeatureMetadata
s@UpdateFeatureMetadata' {} Maybe [Text]
a -> UpdateFeatureMetadata
s {$sel:parameterRemovals:UpdateFeatureMetadata' :: Maybe [Text]
parameterRemovals = Maybe [Text]
a} :: UpdateFeatureMetadata) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

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

instance Core.AWSRequest UpdateFeatureMetadata where
  type
    AWSResponse UpdateFeatureMetadata =
      UpdateFeatureMetadataResponse
  request :: (Service -> Service)
-> UpdateFeatureMetadata -> Request UpdateFeatureMetadata
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 UpdateFeatureMetadata
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateFeatureMetadata)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull UpdateFeatureMetadataResponse
UpdateFeatureMetadataResponse'

instance Prelude.Hashable UpdateFeatureMetadata where
  hashWithSalt :: Int -> UpdateFeatureMetadata -> Int
hashWithSalt Int
_salt UpdateFeatureMetadata' {Maybe [Text]
Maybe [FeatureParameter]
Maybe Text
Text
featureName :: Text
featureGroupName :: Text
parameterRemovals :: Maybe [Text]
parameterAdditions :: Maybe [FeatureParameter]
description :: Maybe Text
$sel:featureName:UpdateFeatureMetadata' :: UpdateFeatureMetadata -> Text
$sel:featureGroupName:UpdateFeatureMetadata' :: UpdateFeatureMetadata -> Text
$sel:parameterRemovals:UpdateFeatureMetadata' :: UpdateFeatureMetadata -> Maybe [Text]
$sel:parameterAdditions:UpdateFeatureMetadata' :: UpdateFeatureMetadata -> Maybe [FeatureParameter]
$sel:description:UpdateFeatureMetadata' :: UpdateFeatureMetadata -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [FeatureParameter]
parameterAdditions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
parameterRemovals
      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 UpdateFeatureMetadata where
  rnf :: UpdateFeatureMetadata -> ()
rnf UpdateFeatureMetadata' {Maybe [Text]
Maybe [FeatureParameter]
Maybe Text
Text
featureName :: Text
featureGroupName :: Text
parameterRemovals :: Maybe [Text]
parameterAdditions :: Maybe [FeatureParameter]
description :: Maybe Text
$sel:featureName:UpdateFeatureMetadata' :: UpdateFeatureMetadata -> Text
$sel:featureGroupName:UpdateFeatureMetadata' :: UpdateFeatureMetadata -> Text
$sel:parameterRemovals:UpdateFeatureMetadata' :: UpdateFeatureMetadata -> Maybe [Text]
$sel:parameterAdditions:UpdateFeatureMetadata' :: UpdateFeatureMetadata -> Maybe [FeatureParameter]
$sel:description:UpdateFeatureMetadata' :: UpdateFeatureMetadata -> 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]
parameterAdditions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
parameterRemovals
      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

instance Data.ToHeaders UpdateFeatureMetadata where
  toHeaders :: UpdateFeatureMetadata -> [Header]
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 -> [Header]
Data.=# ( ByteString
"SageMaker.UpdateFeatureMetadata" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateFeatureMetadata where
  toJSON :: UpdateFeatureMetadata -> Value
toJSON UpdateFeatureMetadata' {Maybe [Text]
Maybe [FeatureParameter]
Maybe Text
Text
featureName :: Text
featureGroupName :: Text
parameterRemovals :: Maybe [Text]
parameterAdditions :: Maybe [FeatureParameter]
description :: Maybe Text
$sel:featureName:UpdateFeatureMetadata' :: UpdateFeatureMetadata -> Text
$sel:featureGroupName:UpdateFeatureMetadata' :: UpdateFeatureMetadata -> Text
$sel:parameterRemovals:UpdateFeatureMetadata' :: UpdateFeatureMetadata -> Maybe [Text]
$sel:parameterAdditions:UpdateFeatureMetadata' :: UpdateFeatureMetadata -> Maybe [FeatureParameter]
$sel:description:UpdateFeatureMetadata' :: UpdateFeatureMetadata -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Description" 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
description,
            (Key
"ParameterAdditions" 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 [FeatureParameter]
parameterAdditions,
            (Key
"ParameterRemovals" 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]
parameterRemovals,
            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 UpdateFeatureMetadata where
  toPath :: UpdateFeatureMetadata -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

-- |
-- Create a value of 'UpdateFeatureMetadataResponse' 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.
newUpdateFeatureMetadataResponse ::
  UpdateFeatureMetadataResponse
newUpdateFeatureMetadataResponse :: UpdateFeatureMetadataResponse
newUpdateFeatureMetadataResponse =
  UpdateFeatureMetadataResponse
UpdateFeatureMetadataResponse'

instance Prelude.NFData UpdateFeatureMetadataResponse where
  rnf :: UpdateFeatureMetadataResponse -> ()
rnf UpdateFeatureMetadataResponse
_ = ()