{-# 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.UpdateUserProfile
-- 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 a user profile.
module Amazonka.SageMaker.UpdateUserProfile
  ( -- * Creating a Request
    UpdateUserProfile (..),
    newUpdateUserProfile,

    -- * Request Lenses
    updateUserProfile_userSettings,
    updateUserProfile_domainId,
    updateUserProfile_userProfileName,

    -- * Destructuring the Response
    UpdateUserProfileResponse (..),
    newUpdateUserProfileResponse,

    -- * Response Lenses
    updateUserProfileResponse_userProfileArn,
    updateUserProfileResponse_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.SageMaker.Types

-- | /See:/ 'newUpdateUserProfile' smart constructor.
data UpdateUserProfile = UpdateUserProfile'
  { -- | A collection of settings.
    UpdateUserProfile -> Maybe UserSettings
userSettings :: Prelude.Maybe UserSettings,
    -- | The domain ID.
    UpdateUserProfile -> Text
domainId :: Prelude.Text,
    -- | The user profile name.
    UpdateUserProfile -> Text
userProfileName :: Prelude.Text
  }
  deriving (UpdateUserProfile -> UpdateUserProfile -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateUserProfile -> UpdateUserProfile -> Bool
$c/= :: UpdateUserProfile -> UpdateUserProfile -> Bool
== :: UpdateUserProfile -> UpdateUserProfile -> Bool
$c== :: UpdateUserProfile -> UpdateUserProfile -> Bool
Prelude.Eq, ReadPrec [UpdateUserProfile]
ReadPrec UpdateUserProfile
Int -> ReadS UpdateUserProfile
ReadS [UpdateUserProfile]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateUserProfile]
$creadListPrec :: ReadPrec [UpdateUserProfile]
readPrec :: ReadPrec UpdateUserProfile
$creadPrec :: ReadPrec UpdateUserProfile
readList :: ReadS [UpdateUserProfile]
$creadList :: ReadS [UpdateUserProfile]
readsPrec :: Int -> ReadS UpdateUserProfile
$creadsPrec :: Int -> ReadS UpdateUserProfile
Prelude.Read, Int -> UpdateUserProfile -> ShowS
[UpdateUserProfile] -> ShowS
UpdateUserProfile -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateUserProfile] -> ShowS
$cshowList :: [UpdateUserProfile] -> ShowS
show :: UpdateUserProfile -> String
$cshow :: UpdateUserProfile -> String
showsPrec :: Int -> UpdateUserProfile -> ShowS
$cshowsPrec :: Int -> UpdateUserProfile -> ShowS
Prelude.Show, forall x. Rep UpdateUserProfile x -> UpdateUserProfile
forall x. UpdateUserProfile -> Rep UpdateUserProfile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateUserProfile x -> UpdateUserProfile
$cfrom :: forall x. UpdateUserProfile -> Rep UpdateUserProfile x
Prelude.Generic)

-- |
-- Create a value of 'UpdateUserProfile' 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:
--
-- 'userSettings', 'updateUserProfile_userSettings' - A collection of settings.
--
-- 'domainId', 'updateUserProfile_domainId' - The domain ID.
--
-- 'userProfileName', 'updateUserProfile_userProfileName' - The user profile name.
newUpdateUserProfile ::
  -- | 'domainId'
  Prelude.Text ->
  -- | 'userProfileName'
  Prelude.Text ->
  UpdateUserProfile
newUpdateUserProfile :: Text -> Text -> UpdateUserProfile
newUpdateUserProfile Text
pDomainId_ Text
pUserProfileName_ =
  UpdateUserProfile'
    { $sel:userSettings:UpdateUserProfile' :: Maybe UserSettings
userSettings = forall a. Maybe a
Prelude.Nothing,
      $sel:domainId:UpdateUserProfile' :: Text
domainId = Text
pDomainId_,
      $sel:userProfileName:UpdateUserProfile' :: Text
userProfileName = Text
pUserProfileName_
    }

-- | A collection of settings.
updateUserProfile_userSettings :: Lens.Lens' UpdateUserProfile (Prelude.Maybe UserSettings)
updateUserProfile_userSettings :: Lens' UpdateUserProfile (Maybe UserSettings)
updateUserProfile_userSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserProfile' {Maybe UserSettings
userSettings :: Maybe UserSettings
$sel:userSettings:UpdateUserProfile' :: UpdateUserProfile -> Maybe UserSettings
userSettings} -> Maybe UserSettings
userSettings) (\s :: UpdateUserProfile
s@UpdateUserProfile' {} Maybe UserSettings
a -> UpdateUserProfile
s {$sel:userSettings:UpdateUserProfile' :: Maybe UserSettings
userSettings = Maybe UserSettings
a} :: UpdateUserProfile)

-- | The domain ID.
updateUserProfile_domainId :: Lens.Lens' UpdateUserProfile Prelude.Text
updateUserProfile_domainId :: Lens' UpdateUserProfile Text
updateUserProfile_domainId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserProfile' {Text
domainId :: Text
$sel:domainId:UpdateUserProfile' :: UpdateUserProfile -> Text
domainId} -> Text
domainId) (\s :: UpdateUserProfile
s@UpdateUserProfile' {} Text
a -> UpdateUserProfile
s {$sel:domainId:UpdateUserProfile' :: Text
domainId = Text
a} :: UpdateUserProfile)

-- | The user profile name.
updateUserProfile_userProfileName :: Lens.Lens' UpdateUserProfile Prelude.Text
updateUserProfile_userProfileName :: Lens' UpdateUserProfile Text
updateUserProfile_userProfileName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserProfile' {Text
userProfileName :: Text
$sel:userProfileName:UpdateUserProfile' :: UpdateUserProfile -> Text
userProfileName} -> Text
userProfileName) (\s :: UpdateUserProfile
s@UpdateUserProfile' {} Text
a -> UpdateUserProfile
s {$sel:userProfileName:UpdateUserProfile' :: Text
userProfileName = Text
a} :: UpdateUserProfile)

instance Core.AWSRequest UpdateUserProfile where
  type
    AWSResponse UpdateUserProfile =
      UpdateUserProfileResponse
  request :: (Service -> Service)
-> UpdateUserProfile -> Request UpdateUserProfile
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 UpdateUserProfile
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateUserProfile)))
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 -> Int -> UpdateUserProfileResponse
UpdateUserProfileResponse'
            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
"UserProfileArn")
            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 UpdateUserProfile where
  hashWithSalt :: Int -> UpdateUserProfile -> Int
hashWithSalt Int
_salt UpdateUserProfile' {Maybe UserSettings
Text
userProfileName :: Text
domainId :: Text
userSettings :: Maybe UserSettings
$sel:userProfileName:UpdateUserProfile' :: UpdateUserProfile -> Text
$sel:domainId:UpdateUserProfile' :: UpdateUserProfile -> Text
$sel:userSettings:UpdateUserProfile' :: UpdateUserProfile -> Maybe UserSettings
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe UserSettings
userSettings
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
domainId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
userProfileName

instance Prelude.NFData UpdateUserProfile where
  rnf :: UpdateUserProfile -> ()
rnf UpdateUserProfile' {Maybe UserSettings
Text
userProfileName :: Text
domainId :: Text
userSettings :: Maybe UserSettings
$sel:userProfileName:UpdateUserProfile' :: UpdateUserProfile -> Text
$sel:domainId:UpdateUserProfile' :: UpdateUserProfile -> Text
$sel:userSettings:UpdateUserProfile' :: UpdateUserProfile -> Maybe UserSettings
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe UserSettings
userSettings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
domainId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
userProfileName

instance Data.ToHeaders UpdateUserProfile where
  toHeaders :: UpdateUserProfile -> 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.UpdateUserProfile" ::
                          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 UpdateUserProfile where
  toJSON :: UpdateUserProfile -> Value
toJSON UpdateUserProfile' {Maybe UserSettings
Text
userProfileName :: Text
domainId :: Text
userSettings :: Maybe UserSettings
$sel:userProfileName:UpdateUserProfile' :: UpdateUserProfile -> Text
$sel:domainId:UpdateUserProfile' :: UpdateUserProfile -> Text
$sel:userSettings:UpdateUserProfile' :: UpdateUserProfile -> Maybe UserSettings
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"UserSettings" 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 UserSettings
userSettings,
            forall a. a -> Maybe a
Prelude.Just (Key
"DomainId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
domainId),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"UserProfileName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
userProfileName)
          ]
      )

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

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

-- | /See:/ 'newUpdateUserProfileResponse' smart constructor.
data UpdateUserProfileResponse = UpdateUserProfileResponse'
  { -- | The user profile Amazon Resource Name (ARN).
    UpdateUserProfileResponse -> Maybe Text
userProfileArn :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdateUserProfileResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateUserProfileResponse -> UpdateUserProfileResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateUserProfileResponse -> UpdateUserProfileResponse -> Bool
$c/= :: UpdateUserProfileResponse -> UpdateUserProfileResponse -> Bool
== :: UpdateUserProfileResponse -> UpdateUserProfileResponse -> Bool
$c== :: UpdateUserProfileResponse -> UpdateUserProfileResponse -> Bool
Prelude.Eq, ReadPrec [UpdateUserProfileResponse]
ReadPrec UpdateUserProfileResponse
Int -> ReadS UpdateUserProfileResponse
ReadS [UpdateUserProfileResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateUserProfileResponse]
$creadListPrec :: ReadPrec [UpdateUserProfileResponse]
readPrec :: ReadPrec UpdateUserProfileResponse
$creadPrec :: ReadPrec UpdateUserProfileResponse
readList :: ReadS [UpdateUserProfileResponse]
$creadList :: ReadS [UpdateUserProfileResponse]
readsPrec :: Int -> ReadS UpdateUserProfileResponse
$creadsPrec :: Int -> ReadS UpdateUserProfileResponse
Prelude.Read, Int -> UpdateUserProfileResponse -> ShowS
[UpdateUserProfileResponse] -> ShowS
UpdateUserProfileResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateUserProfileResponse] -> ShowS
$cshowList :: [UpdateUserProfileResponse] -> ShowS
show :: UpdateUserProfileResponse -> String
$cshow :: UpdateUserProfileResponse -> String
showsPrec :: Int -> UpdateUserProfileResponse -> ShowS
$cshowsPrec :: Int -> UpdateUserProfileResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateUserProfileResponse x -> UpdateUserProfileResponse
forall x.
UpdateUserProfileResponse -> Rep UpdateUserProfileResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateUserProfileResponse x -> UpdateUserProfileResponse
$cfrom :: forall x.
UpdateUserProfileResponse -> Rep UpdateUserProfileResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateUserProfileResponse' 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:
--
-- 'userProfileArn', 'updateUserProfileResponse_userProfileArn' - The user profile Amazon Resource Name (ARN).
--
-- 'httpStatus', 'updateUserProfileResponse_httpStatus' - The response's http status code.
newUpdateUserProfileResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateUserProfileResponse
newUpdateUserProfileResponse :: Int -> UpdateUserProfileResponse
newUpdateUserProfileResponse Int
pHttpStatus_ =
  UpdateUserProfileResponse'
    { $sel:userProfileArn:UpdateUserProfileResponse' :: Maybe Text
userProfileArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateUserProfileResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The user profile Amazon Resource Name (ARN).
updateUserProfileResponse_userProfileArn :: Lens.Lens' UpdateUserProfileResponse (Prelude.Maybe Prelude.Text)
updateUserProfileResponse_userProfileArn :: Lens' UpdateUserProfileResponse (Maybe Text)
updateUserProfileResponse_userProfileArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserProfileResponse' {Maybe Text
userProfileArn :: Maybe Text
$sel:userProfileArn:UpdateUserProfileResponse' :: UpdateUserProfileResponse -> Maybe Text
userProfileArn} -> Maybe Text
userProfileArn) (\s :: UpdateUserProfileResponse
s@UpdateUserProfileResponse' {} Maybe Text
a -> UpdateUserProfileResponse
s {$sel:userProfileArn:UpdateUserProfileResponse' :: Maybe Text
userProfileArn = Maybe Text
a} :: UpdateUserProfileResponse)

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

instance Prelude.NFData UpdateUserProfileResponse where
  rnf :: UpdateUserProfileResponse -> ()
rnf UpdateUserProfileResponse' {Int
Maybe Text
httpStatus :: Int
userProfileArn :: Maybe Text
$sel:httpStatus:UpdateUserProfileResponse' :: UpdateUserProfileResponse -> Int
$sel:userProfileArn:UpdateUserProfileResponse' :: UpdateUserProfileResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
userProfileArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus