{-# 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.DataBrew.UpdateProject
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Modifies the definition of an existing DataBrew project.
module Amazonka.DataBrew.UpdateProject
  ( -- * Creating a Request
    UpdateProject (..),
    newUpdateProject,

    -- * Request Lenses
    updateProject_sample,
    updateProject_roleArn,
    updateProject_name,

    -- * Destructuring the Response
    UpdateProjectResponse (..),
    newUpdateProjectResponse,

    -- * Response Lenses
    updateProjectResponse_lastModifiedDate,
    updateProjectResponse_httpStatus,
    updateProjectResponse_name,
  )
where

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

-- | /See:/ 'newUpdateProject' smart constructor.
data UpdateProject = UpdateProject'
  { UpdateProject -> Maybe Sample
sample :: Prelude.Maybe Sample,
    -- | The Amazon Resource Name (ARN) of the IAM role to be assumed for this
    -- request.
    UpdateProject -> Text
roleArn :: Prelude.Text,
    -- | The name of the project to be updated.
    UpdateProject -> Text
name :: Prelude.Text
  }
  deriving (UpdateProject -> UpdateProject -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateProject -> UpdateProject -> Bool
$c/= :: UpdateProject -> UpdateProject -> Bool
== :: UpdateProject -> UpdateProject -> Bool
$c== :: UpdateProject -> UpdateProject -> Bool
Prelude.Eq, ReadPrec [UpdateProject]
ReadPrec UpdateProject
Int -> ReadS UpdateProject
ReadS [UpdateProject]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateProject]
$creadListPrec :: ReadPrec [UpdateProject]
readPrec :: ReadPrec UpdateProject
$creadPrec :: ReadPrec UpdateProject
readList :: ReadS [UpdateProject]
$creadList :: ReadS [UpdateProject]
readsPrec :: Int -> ReadS UpdateProject
$creadsPrec :: Int -> ReadS UpdateProject
Prelude.Read, Int -> UpdateProject -> ShowS
[UpdateProject] -> ShowS
UpdateProject -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateProject] -> ShowS
$cshowList :: [UpdateProject] -> ShowS
show :: UpdateProject -> String
$cshow :: UpdateProject -> String
showsPrec :: Int -> UpdateProject -> ShowS
$cshowsPrec :: Int -> UpdateProject -> ShowS
Prelude.Show, forall x. Rep UpdateProject x -> UpdateProject
forall x. UpdateProject -> Rep UpdateProject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateProject x -> UpdateProject
$cfrom :: forall x. UpdateProject -> Rep UpdateProject x
Prelude.Generic)

-- |
-- Create a value of 'UpdateProject' 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:
--
-- 'sample', 'updateProject_sample' - Undocumented member.
--
-- 'roleArn', 'updateProject_roleArn' - The Amazon Resource Name (ARN) of the IAM role to be assumed for this
-- request.
--
-- 'name', 'updateProject_name' - The name of the project to be updated.
newUpdateProject ::
  -- | 'roleArn'
  Prelude.Text ->
  -- | 'name'
  Prelude.Text ->
  UpdateProject
newUpdateProject :: Text -> Text -> UpdateProject
newUpdateProject Text
pRoleArn_ Text
pName_ =
  UpdateProject'
    { $sel:sample:UpdateProject' :: Maybe Sample
sample = forall a. Maybe a
Prelude.Nothing,
      $sel:roleArn:UpdateProject' :: Text
roleArn = Text
pRoleArn_,
      $sel:name:UpdateProject' :: Text
name = Text
pName_
    }

-- | Undocumented member.
updateProject_sample :: Lens.Lens' UpdateProject (Prelude.Maybe Sample)
updateProject_sample :: Lens' UpdateProject (Maybe Sample)
updateProject_sample = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProject' {Maybe Sample
sample :: Maybe Sample
$sel:sample:UpdateProject' :: UpdateProject -> Maybe Sample
sample} -> Maybe Sample
sample) (\s :: UpdateProject
s@UpdateProject' {} Maybe Sample
a -> UpdateProject
s {$sel:sample:UpdateProject' :: Maybe Sample
sample = Maybe Sample
a} :: UpdateProject)

-- | The Amazon Resource Name (ARN) of the IAM role to be assumed for this
-- request.
updateProject_roleArn :: Lens.Lens' UpdateProject Prelude.Text
updateProject_roleArn :: Lens' UpdateProject Text
updateProject_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProject' {Text
roleArn :: Text
$sel:roleArn:UpdateProject' :: UpdateProject -> Text
roleArn} -> Text
roleArn) (\s :: UpdateProject
s@UpdateProject' {} Text
a -> UpdateProject
s {$sel:roleArn:UpdateProject' :: Text
roleArn = Text
a} :: UpdateProject)

-- | The name of the project to be updated.
updateProject_name :: Lens.Lens' UpdateProject Prelude.Text
updateProject_name :: Lens' UpdateProject Text
updateProject_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProject' {Text
name :: Text
$sel:name:UpdateProject' :: UpdateProject -> Text
name} -> Text
name) (\s :: UpdateProject
s@UpdateProject' {} Text
a -> UpdateProject
s {$sel:name:UpdateProject' :: Text
name = Text
a} :: UpdateProject)

instance Core.AWSRequest UpdateProject where
  type
    AWSResponse UpdateProject =
      UpdateProjectResponse
  request :: (Service -> Service) -> UpdateProject -> Request UpdateProject
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateProject
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateProject)))
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 POSIX -> Int -> Text -> UpdateProjectResponse
UpdateProjectResponse'
            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
"LastModifiedDate")
            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
"Name")
      )

instance Prelude.Hashable UpdateProject where
  hashWithSalt :: Int -> UpdateProject -> Int
hashWithSalt Int
_salt UpdateProject' {Maybe Sample
Text
name :: Text
roleArn :: Text
sample :: Maybe Sample
$sel:name:UpdateProject' :: UpdateProject -> Text
$sel:roleArn:UpdateProject' :: UpdateProject -> Text
$sel:sample:UpdateProject' :: UpdateProject -> Maybe Sample
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Sample
sample
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
roleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData UpdateProject where
  rnf :: UpdateProject -> ()
rnf UpdateProject' {Maybe Sample
Text
name :: Text
roleArn :: Text
sample :: Maybe Sample
$sel:name:UpdateProject' :: UpdateProject -> Text
$sel:roleArn:UpdateProject' :: UpdateProject -> Text
$sel:sample:UpdateProject' :: UpdateProject -> Maybe Sample
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Sample
sample
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
roleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name

instance Data.ToHeaders UpdateProject where
  toHeaders :: UpdateProject -> 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.ToJSON UpdateProject where
  toJSON :: UpdateProject -> Value
toJSON UpdateProject' {Maybe Sample
Text
name :: Text
roleArn :: Text
sample :: Maybe Sample
$sel:name:UpdateProject' :: UpdateProject -> Text
$sel:roleArn:UpdateProject' :: UpdateProject -> Text
$sel:sample:UpdateProject' :: UpdateProject -> Maybe Sample
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Sample" 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 Sample
sample,
            forall a. a -> Maybe a
Prelude.Just (Key
"RoleArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
roleArn)
          ]
      )

instance Data.ToPath UpdateProject where
  toPath :: UpdateProject -> ByteString
toPath UpdateProject' {Maybe Sample
Text
name :: Text
roleArn :: Text
sample :: Maybe Sample
$sel:name:UpdateProject' :: UpdateProject -> Text
$sel:roleArn:UpdateProject' :: UpdateProject -> Text
$sel:sample:UpdateProject' :: UpdateProject -> Maybe Sample
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/projects/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
name]

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

-- | /See:/ 'newUpdateProjectResponse' smart constructor.
data UpdateProjectResponse = UpdateProjectResponse'
  { -- | The date and time that the project was last modified.
    UpdateProjectResponse -> Maybe POSIX
lastModifiedDate :: Prelude.Maybe Data.POSIX,
    -- | The response's http status code.
    UpdateProjectResponse -> Int
httpStatus :: Prelude.Int,
    -- | The name of the project that you updated.
    UpdateProjectResponse -> Text
name :: Prelude.Text
  }
  deriving (UpdateProjectResponse -> UpdateProjectResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateProjectResponse -> UpdateProjectResponse -> Bool
$c/= :: UpdateProjectResponse -> UpdateProjectResponse -> Bool
== :: UpdateProjectResponse -> UpdateProjectResponse -> Bool
$c== :: UpdateProjectResponse -> UpdateProjectResponse -> Bool
Prelude.Eq, ReadPrec [UpdateProjectResponse]
ReadPrec UpdateProjectResponse
Int -> ReadS UpdateProjectResponse
ReadS [UpdateProjectResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateProjectResponse]
$creadListPrec :: ReadPrec [UpdateProjectResponse]
readPrec :: ReadPrec UpdateProjectResponse
$creadPrec :: ReadPrec UpdateProjectResponse
readList :: ReadS [UpdateProjectResponse]
$creadList :: ReadS [UpdateProjectResponse]
readsPrec :: Int -> ReadS UpdateProjectResponse
$creadsPrec :: Int -> ReadS UpdateProjectResponse
Prelude.Read, Int -> UpdateProjectResponse -> ShowS
[UpdateProjectResponse] -> ShowS
UpdateProjectResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateProjectResponse] -> ShowS
$cshowList :: [UpdateProjectResponse] -> ShowS
show :: UpdateProjectResponse -> String
$cshow :: UpdateProjectResponse -> String
showsPrec :: Int -> UpdateProjectResponse -> ShowS
$cshowsPrec :: Int -> UpdateProjectResponse -> ShowS
Prelude.Show, forall x. Rep UpdateProjectResponse x -> UpdateProjectResponse
forall x. UpdateProjectResponse -> Rep UpdateProjectResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateProjectResponse x -> UpdateProjectResponse
$cfrom :: forall x. UpdateProjectResponse -> Rep UpdateProjectResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateProjectResponse' 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:
--
-- 'lastModifiedDate', 'updateProjectResponse_lastModifiedDate' - The date and time that the project was last modified.
--
-- 'httpStatus', 'updateProjectResponse_httpStatus' - The response's http status code.
--
-- 'name', 'updateProjectResponse_name' - The name of the project that you updated.
newUpdateProjectResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'name'
  Prelude.Text ->
  UpdateProjectResponse
newUpdateProjectResponse :: Int -> Text -> UpdateProjectResponse
newUpdateProjectResponse Int
pHttpStatus_ Text
pName_ =
  UpdateProjectResponse'
    { $sel:lastModifiedDate:UpdateProjectResponse' :: Maybe POSIX
lastModifiedDate =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateProjectResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:name:UpdateProjectResponse' :: Text
name = Text
pName_
    }

-- | The date and time that the project was last modified.
updateProjectResponse_lastModifiedDate :: Lens.Lens' UpdateProjectResponse (Prelude.Maybe Prelude.UTCTime)
updateProjectResponse_lastModifiedDate :: Lens' UpdateProjectResponse (Maybe UTCTime)
updateProjectResponse_lastModifiedDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProjectResponse' {Maybe POSIX
lastModifiedDate :: Maybe POSIX
$sel:lastModifiedDate:UpdateProjectResponse' :: UpdateProjectResponse -> Maybe POSIX
lastModifiedDate} -> Maybe POSIX
lastModifiedDate) (\s :: UpdateProjectResponse
s@UpdateProjectResponse' {} Maybe POSIX
a -> UpdateProjectResponse
s {$sel:lastModifiedDate:UpdateProjectResponse' :: Maybe POSIX
lastModifiedDate = Maybe POSIX
a} :: UpdateProjectResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

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

-- | The name of the project that you updated.
updateProjectResponse_name :: Lens.Lens' UpdateProjectResponse Prelude.Text
updateProjectResponse_name :: Lens' UpdateProjectResponse Text
updateProjectResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProjectResponse' {Text
name :: Text
$sel:name:UpdateProjectResponse' :: UpdateProjectResponse -> Text
name} -> Text
name) (\s :: UpdateProjectResponse
s@UpdateProjectResponse' {} Text
a -> UpdateProjectResponse
s {$sel:name:UpdateProjectResponse' :: Text
name = Text
a} :: UpdateProjectResponse)

instance Prelude.NFData UpdateProjectResponse where
  rnf :: UpdateProjectResponse -> ()
rnf UpdateProjectResponse' {Int
Maybe POSIX
Text
name :: Text
httpStatus :: Int
lastModifiedDate :: Maybe POSIX
$sel:name:UpdateProjectResponse' :: UpdateProjectResponse -> Text
$sel:httpStatus:UpdateProjectResponse' :: UpdateProjectResponse -> Int
$sel:lastModifiedDate:UpdateProjectResponse' :: UpdateProjectResponse -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastModifiedDate
      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
name