{-# 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.Mobile.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)
--
-- Update an existing project.
module Amazonka.Mobile.UpdateProject
  ( -- * Creating a Request
    UpdateProject (..),
    newUpdateProject,

    -- * Request Lenses
    updateProject_contents,
    updateProject_projectId,

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

    -- * Response Lenses
    updateProjectResponse_details,
    updateProjectResponse_httpStatus,
  )
where

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

-- | Request structure used for requests to update project configuration.
--
-- /See:/ 'newUpdateProject' smart constructor.
data UpdateProject = UpdateProject'
  { -- | ZIP or YAML file which contains project configuration to be updated.
    -- This should be the contents of the file downloaded from the URL provided
    -- in an export project operation.
    UpdateProject -> Maybe ByteString
contents :: Prelude.Maybe Prelude.ByteString,
    -- | Unique project identifier.
    UpdateProject -> Text
projectId :: 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:
--
-- 'contents', 'updateProject_contents' - ZIP or YAML file which contains project configuration to be updated.
-- This should be the contents of the file downloaded from the URL provided
-- in an export project operation.
--
-- 'projectId', 'updateProject_projectId' - Unique project identifier.
newUpdateProject ::
  -- | 'projectId'
  Prelude.Text ->
  UpdateProject
newUpdateProject :: Text -> UpdateProject
newUpdateProject Text
pProjectId_ =
  UpdateProject'
    { $sel:contents:UpdateProject' :: Maybe ByteString
contents = forall a. Maybe a
Prelude.Nothing,
      $sel:projectId:UpdateProject' :: Text
projectId = Text
pProjectId_
    }

-- | ZIP or YAML file which contains project configuration to be updated.
-- This should be the contents of the file downloaded from the URL provided
-- in an export project operation.
updateProject_contents :: Lens.Lens' UpdateProject (Prelude.Maybe Prelude.ByteString)
updateProject_contents :: Lens' UpdateProject (Maybe ByteString)
updateProject_contents = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProject' {Maybe ByteString
contents :: Maybe ByteString
$sel:contents:UpdateProject' :: UpdateProject -> Maybe ByteString
contents} -> Maybe ByteString
contents) (\s :: UpdateProject
s@UpdateProject' {} Maybe ByteString
a -> UpdateProject
s {$sel:contents:UpdateProject' :: Maybe ByteString
contents = Maybe ByteString
a} :: UpdateProject)

-- | Unique project identifier.
updateProject_projectId :: Lens.Lens' UpdateProject Prelude.Text
updateProject_projectId :: Lens' UpdateProject Text
updateProject_projectId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProject' {Text
projectId :: Text
$sel:projectId:UpdateProject' :: UpdateProject -> Text
projectId} -> Text
projectId) (\s :: UpdateProject
s@UpdateProject' {} Text
a -> UpdateProject
s {$sel:projectId:UpdateProject' :: Text
projectId = 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, ToBody a) => Service -> a -> Request a
Request.postBody (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 ProjectDetails -> Int -> 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
"details")
            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 UpdateProject where
  hashWithSalt :: Int -> UpdateProject -> Int
hashWithSalt Int
_salt UpdateProject' {Maybe ByteString
Text
projectId :: Text
contents :: Maybe ByteString
$sel:projectId:UpdateProject' :: UpdateProject -> Text
$sel:contents:UpdateProject' :: UpdateProject -> Maybe ByteString
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ByteString
contents
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
projectId

instance Prelude.NFData UpdateProject where
  rnf :: UpdateProject -> ()
rnf UpdateProject' {Maybe ByteString
Text
projectId :: Text
contents :: Maybe ByteString
$sel:projectId:UpdateProject' :: UpdateProject -> Text
$sel:contents:UpdateProject' :: UpdateProject -> Maybe ByteString
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ByteString
contents
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
projectId

instance Data.ToBody UpdateProject where
  toBody :: UpdateProject -> RequestBody
toBody UpdateProject' {Maybe ByteString
Text
projectId :: Text
contents :: Maybe ByteString
$sel:projectId:UpdateProject' :: UpdateProject -> Text
$sel:contents:UpdateProject' :: UpdateProject -> Maybe ByteString
..} = forall a. ToBody a => a -> RequestBody
Data.toBody Maybe ByteString
contents

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.ToPath UpdateProject where
  toPath :: UpdateProject -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/update"

instance Data.ToQuery UpdateProject where
  toQuery :: UpdateProject -> QueryString
toQuery UpdateProject' {Maybe ByteString
Text
projectId :: Text
contents :: Maybe ByteString
$sel:projectId:UpdateProject' :: UpdateProject -> Text
$sel:contents:UpdateProject' :: UpdateProject -> Maybe ByteString
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"projectId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
projectId]

-- | Result structure used for requests to updated project configuration.
--
-- /See:/ 'newUpdateProjectResponse' smart constructor.
data UpdateProjectResponse = UpdateProjectResponse'
  { -- | Detailed information about the updated AWS Mobile Hub project.
    UpdateProjectResponse -> Maybe ProjectDetails
details :: Prelude.Maybe ProjectDetails,
    -- | The response's http status code.
    UpdateProjectResponse -> Int
httpStatus :: Prelude.Int
  }
  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:
--
-- 'details', 'updateProjectResponse_details' - Detailed information about the updated AWS Mobile Hub project.
--
-- 'httpStatus', 'updateProjectResponse_httpStatus' - The response's http status code.
newUpdateProjectResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateProjectResponse
newUpdateProjectResponse :: Int -> UpdateProjectResponse
newUpdateProjectResponse Int
pHttpStatus_ =
  UpdateProjectResponse'
    { $sel:details:UpdateProjectResponse' :: Maybe ProjectDetails
details = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateProjectResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Detailed information about the updated AWS Mobile Hub project.
updateProjectResponse_details :: Lens.Lens' UpdateProjectResponse (Prelude.Maybe ProjectDetails)
updateProjectResponse_details :: Lens' UpdateProjectResponse (Maybe ProjectDetails)
updateProjectResponse_details = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProjectResponse' {Maybe ProjectDetails
details :: Maybe ProjectDetails
$sel:details:UpdateProjectResponse' :: UpdateProjectResponse -> Maybe ProjectDetails
details} -> Maybe ProjectDetails
details) (\s :: UpdateProjectResponse
s@UpdateProjectResponse' {} Maybe ProjectDetails
a -> UpdateProjectResponse
s {$sel:details:UpdateProjectResponse' :: Maybe ProjectDetails
details = Maybe ProjectDetails
a} :: UpdateProjectResponse)

-- | 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)

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