{-# 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.UpdateFeatureGroup
-- 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 feature group.
module Amazonka.SageMaker.UpdateFeatureGroup
  ( -- * Creating a Request
    UpdateFeatureGroup (..),
    newUpdateFeatureGroup,

    -- * Request Lenses
    updateFeatureGroup_featureAdditions,
    updateFeatureGroup_featureGroupName,

    -- * Destructuring the Response
    UpdateFeatureGroupResponse (..),
    newUpdateFeatureGroupResponse,

    -- * Response Lenses
    updateFeatureGroupResponse_httpStatus,
    updateFeatureGroupResponse_featureGroupArn,
  )
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:/ 'newUpdateFeatureGroup' smart constructor.
data UpdateFeatureGroup = UpdateFeatureGroup'
  { -- | Updates the feature group. Updating a feature group is an asynchronous
    -- operation. When you get an HTTP 200 response, you\'ve made a valid
    -- request. It takes some time after you\'ve made a valid request for
    -- Feature Store to update the feature group.
    UpdateFeatureGroup -> Maybe (NonEmpty FeatureDefinition)
featureAdditions :: Prelude.Maybe (Prelude.NonEmpty FeatureDefinition),
    -- | The name of the feature group that you\'re updating.
    UpdateFeatureGroup -> Text
featureGroupName :: Prelude.Text
  }
  deriving (UpdateFeatureGroup -> UpdateFeatureGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateFeatureGroup -> UpdateFeatureGroup -> Bool
$c/= :: UpdateFeatureGroup -> UpdateFeatureGroup -> Bool
== :: UpdateFeatureGroup -> UpdateFeatureGroup -> Bool
$c== :: UpdateFeatureGroup -> UpdateFeatureGroup -> Bool
Prelude.Eq, ReadPrec [UpdateFeatureGroup]
ReadPrec UpdateFeatureGroup
Int -> ReadS UpdateFeatureGroup
ReadS [UpdateFeatureGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateFeatureGroup]
$creadListPrec :: ReadPrec [UpdateFeatureGroup]
readPrec :: ReadPrec UpdateFeatureGroup
$creadPrec :: ReadPrec UpdateFeatureGroup
readList :: ReadS [UpdateFeatureGroup]
$creadList :: ReadS [UpdateFeatureGroup]
readsPrec :: Int -> ReadS UpdateFeatureGroup
$creadsPrec :: Int -> ReadS UpdateFeatureGroup
Prelude.Read, Int -> UpdateFeatureGroup -> ShowS
[UpdateFeatureGroup] -> ShowS
UpdateFeatureGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateFeatureGroup] -> ShowS
$cshowList :: [UpdateFeatureGroup] -> ShowS
show :: UpdateFeatureGroup -> String
$cshow :: UpdateFeatureGroup -> String
showsPrec :: Int -> UpdateFeatureGroup -> ShowS
$cshowsPrec :: Int -> UpdateFeatureGroup -> ShowS
Prelude.Show, forall x. Rep UpdateFeatureGroup x -> UpdateFeatureGroup
forall x. UpdateFeatureGroup -> Rep UpdateFeatureGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateFeatureGroup x -> UpdateFeatureGroup
$cfrom :: forall x. UpdateFeatureGroup -> Rep UpdateFeatureGroup x
Prelude.Generic)

-- |
-- Create a value of 'UpdateFeatureGroup' 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:
--
-- 'featureAdditions', 'updateFeatureGroup_featureAdditions' - Updates the feature group. Updating a feature group is an asynchronous
-- operation. When you get an HTTP 200 response, you\'ve made a valid
-- request. It takes some time after you\'ve made a valid request for
-- Feature Store to update the feature group.
--
-- 'featureGroupName', 'updateFeatureGroup_featureGroupName' - The name of the feature group that you\'re updating.
newUpdateFeatureGroup ::
  -- | 'featureGroupName'
  Prelude.Text ->
  UpdateFeatureGroup
newUpdateFeatureGroup :: Text -> UpdateFeatureGroup
newUpdateFeatureGroup Text
pFeatureGroupName_ =
  UpdateFeatureGroup'
    { $sel:featureAdditions:UpdateFeatureGroup' :: Maybe (NonEmpty FeatureDefinition)
featureAdditions =
        forall a. Maybe a
Prelude.Nothing,
      $sel:featureGroupName:UpdateFeatureGroup' :: Text
featureGroupName = Text
pFeatureGroupName_
    }

-- | Updates the feature group. Updating a feature group is an asynchronous
-- operation. When you get an HTTP 200 response, you\'ve made a valid
-- request. It takes some time after you\'ve made a valid request for
-- Feature Store to update the feature group.
updateFeatureGroup_featureAdditions :: Lens.Lens' UpdateFeatureGroup (Prelude.Maybe (Prelude.NonEmpty FeatureDefinition))
updateFeatureGroup_featureAdditions :: Lens' UpdateFeatureGroup (Maybe (NonEmpty FeatureDefinition))
updateFeatureGroup_featureAdditions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFeatureGroup' {Maybe (NonEmpty FeatureDefinition)
featureAdditions :: Maybe (NonEmpty FeatureDefinition)
$sel:featureAdditions:UpdateFeatureGroup' :: UpdateFeatureGroup -> Maybe (NonEmpty FeatureDefinition)
featureAdditions} -> Maybe (NonEmpty FeatureDefinition)
featureAdditions) (\s :: UpdateFeatureGroup
s@UpdateFeatureGroup' {} Maybe (NonEmpty FeatureDefinition)
a -> UpdateFeatureGroup
s {$sel:featureAdditions:UpdateFeatureGroup' :: Maybe (NonEmpty FeatureDefinition)
featureAdditions = Maybe (NonEmpty FeatureDefinition)
a} :: UpdateFeatureGroup) 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 that you\'re updating.
updateFeatureGroup_featureGroupName :: Lens.Lens' UpdateFeatureGroup Prelude.Text
updateFeatureGroup_featureGroupName :: Lens' UpdateFeatureGroup Text
updateFeatureGroup_featureGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFeatureGroup' {Text
featureGroupName :: Text
$sel:featureGroupName:UpdateFeatureGroup' :: UpdateFeatureGroup -> Text
featureGroupName} -> Text
featureGroupName) (\s :: UpdateFeatureGroup
s@UpdateFeatureGroup' {} Text
a -> UpdateFeatureGroup
s {$sel:featureGroupName:UpdateFeatureGroup' :: Text
featureGroupName = Text
a} :: UpdateFeatureGroup)

instance Core.AWSRequest UpdateFeatureGroup where
  type
    AWSResponse UpdateFeatureGroup =
      UpdateFeatureGroupResponse
  request :: (Service -> Service)
-> UpdateFeatureGroup -> Request UpdateFeatureGroup
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 UpdateFeatureGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateFeatureGroup)))
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 ->
          Int -> Text -> UpdateFeatureGroupResponse
UpdateFeatureGroupResponse'
            forall (f :: * -> *) a b. Functor 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")
      )

instance Prelude.Hashable UpdateFeatureGroup where
  hashWithSalt :: Int -> UpdateFeatureGroup -> Int
hashWithSalt Int
_salt UpdateFeatureGroup' {Maybe (NonEmpty FeatureDefinition)
Text
featureGroupName :: Text
featureAdditions :: Maybe (NonEmpty FeatureDefinition)
$sel:featureGroupName:UpdateFeatureGroup' :: UpdateFeatureGroup -> Text
$sel:featureAdditions:UpdateFeatureGroup' :: UpdateFeatureGroup -> Maybe (NonEmpty FeatureDefinition)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty FeatureDefinition)
featureAdditions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
featureGroupName

instance Prelude.NFData UpdateFeatureGroup where
  rnf :: UpdateFeatureGroup -> ()
rnf UpdateFeatureGroup' {Maybe (NonEmpty FeatureDefinition)
Text
featureGroupName :: Text
featureAdditions :: Maybe (NonEmpty FeatureDefinition)
$sel:featureGroupName:UpdateFeatureGroup' :: UpdateFeatureGroup -> Text
$sel:featureAdditions:UpdateFeatureGroup' :: UpdateFeatureGroup -> Maybe (NonEmpty FeatureDefinition)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty FeatureDefinition)
featureAdditions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
featureGroupName

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

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

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

-- | /See:/ 'newUpdateFeatureGroupResponse' smart constructor.
data UpdateFeatureGroupResponse = UpdateFeatureGroupResponse'
  { -- | The response's http status code.
    UpdateFeatureGroupResponse -> Int
httpStatus :: Prelude.Int,
    -- | The Amazon Resource Number (ARN) of the feature group that you\'re
    -- updating.
    UpdateFeatureGroupResponse -> Text
featureGroupArn :: Prelude.Text
  }
  deriving (UpdateFeatureGroupResponse -> UpdateFeatureGroupResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateFeatureGroupResponse -> UpdateFeatureGroupResponse -> Bool
$c/= :: UpdateFeatureGroupResponse -> UpdateFeatureGroupResponse -> Bool
== :: UpdateFeatureGroupResponse -> UpdateFeatureGroupResponse -> Bool
$c== :: UpdateFeatureGroupResponse -> UpdateFeatureGroupResponse -> Bool
Prelude.Eq, ReadPrec [UpdateFeatureGroupResponse]
ReadPrec UpdateFeatureGroupResponse
Int -> ReadS UpdateFeatureGroupResponse
ReadS [UpdateFeatureGroupResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateFeatureGroupResponse]
$creadListPrec :: ReadPrec [UpdateFeatureGroupResponse]
readPrec :: ReadPrec UpdateFeatureGroupResponse
$creadPrec :: ReadPrec UpdateFeatureGroupResponse
readList :: ReadS [UpdateFeatureGroupResponse]
$creadList :: ReadS [UpdateFeatureGroupResponse]
readsPrec :: Int -> ReadS UpdateFeatureGroupResponse
$creadsPrec :: Int -> ReadS UpdateFeatureGroupResponse
Prelude.Read, Int -> UpdateFeatureGroupResponse -> ShowS
[UpdateFeatureGroupResponse] -> ShowS
UpdateFeatureGroupResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateFeatureGroupResponse] -> ShowS
$cshowList :: [UpdateFeatureGroupResponse] -> ShowS
show :: UpdateFeatureGroupResponse -> String
$cshow :: UpdateFeatureGroupResponse -> String
showsPrec :: Int -> UpdateFeatureGroupResponse -> ShowS
$cshowsPrec :: Int -> UpdateFeatureGroupResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateFeatureGroupResponse x -> UpdateFeatureGroupResponse
forall x.
UpdateFeatureGroupResponse -> Rep UpdateFeatureGroupResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateFeatureGroupResponse x -> UpdateFeatureGroupResponse
$cfrom :: forall x.
UpdateFeatureGroupResponse -> Rep UpdateFeatureGroupResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateFeatureGroupResponse' 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:
--
-- 'httpStatus', 'updateFeatureGroupResponse_httpStatus' - The response's http status code.
--
-- 'featureGroupArn', 'updateFeatureGroupResponse_featureGroupArn' - The Amazon Resource Number (ARN) of the feature group that you\'re
-- updating.
newUpdateFeatureGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'featureGroupArn'
  Prelude.Text ->
  UpdateFeatureGroupResponse
newUpdateFeatureGroupResponse :: Int -> Text -> UpdateFeatureGroupResponse
newUpdateFeatureGroupResponse
  Int
pHttpStatus_
  Text
pFeatureGroupArn_ =
    UpdateFeatureGroupResponse'
      { $sel:httpStatus:UpdateFeatureGroupResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:featureGroupArn:UpdateFeatureGroupResponse' :: Text
featureGroupArn = Text
pFeatureGroupArn_
      }

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

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

instance Prelude.NFData UpdateFeatureGroupResponse where
  rnf :: UpdateFeatureGroupResponse -> ()
rnf UpdateFeatureGroupResponse' {Int
Text
featureGroupArn :: Text
httpStatus :: Int
$sel:featureGroupArn:UpdateFeatureGroupResponse' :: UpdateFeatureGroupResponse -> Text
$sel:httpStatus:UpdateFeatureGroupResponse' :: UpdateFeatureGroupResponse -> Int
..} =
    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