{-# 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.DeviceFarm.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 specified project name, given the project ARN and a new
-- name.
module Amazonka.DeviceFarm.UpdateProject
  ( -- * Creating a Request
    UpdateProject (..),
    newUpdateProject,

    -- * Request Lenses
    updateProject_defaultJobTimeoutMinutes,
    updateProject_name,
    updateProject_vpcConfig,
    updateProject_arn,

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

    -- * Response Lenses
    updateProjectResponse_project,
    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.DeviceFarm.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | Represents a request to the update project operation.
--
-- /See:/ 'newUpdateProject' smart constructor.
data UpdateProject = UpdateProject'
  { -- | The number of minutes a test run in the project executes before it times
    -- out.
    UpdateProject -> Maybe Int
defaultJobTimeoutMinutes :: Prelude.Maybe Prelude.Int,
    -- | A string that represents the new name of the project that you are
    -- updating.
    UpdateProject -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The VPC security groups and subnets that are attached to a project.
    UpdateProject -> Maybe VpcConfig
vpcConfig :: Prelude.Maybe VpcConfig,
    -- | The Amazon Resource Name (ARN) of the project whose name to update.
    UpdateProject -> Text
arn :: 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:
--
-- 'defaultJobTimeoutMinutes', 'updateProject_defaultJobTimeoutMinutes' - The number of minutes a test run in the project executes before it times
-- out.
--
-- 'name', 'updateProject_name' - A string that represents the new name of the project that you are
-- updating.
--
-- 'vpcConfig', 'updateProject_vpcConfig' - The VPC security groups and subnets that are attached to a project.
--
-- 'arn', 'updateProject_arn' - The Amazon Resource Name (ARN) of the project whose name to update.
newUpdateProject ::
  -- | 'arn'
  Prelude.Text ->
  UpdateProject
newUpdateProject :: Text -> UpdateProject
newUpdateProject Text
pArn_ =
  UpdateProject'
    { $sel:defaultJobTimeoutMinutes:UpdateProject' :: Maybe Int
defaultJobTimeoutMinutes =
        forall a. Maybe a
Prelude.Nothing,
      $sel:name:UpdateProject' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcConfig:UpdateProject' :: Maybe VpcConfig
vpcConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:arn:UpdateProject' :: Text
arn = Text
pArn_
    }

-- | The number of minutes a test run in the project executes before it times
-- out.
updateProject_defaultJobTimeoutMinutes :: Lens.Lens' UpdateProject (Prelude.Maybe Prelude.Int)
updateProject_defaultJobTimeoutMinutes :: Lens' UpdateProject (Maybe Int)
updateProject_defaultJobTimeoutMinutes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProject' {Maybe Int
defaultJobTimeoutMinutes :: Maybe Int
$sel:defaultJobTimeoutMinutes:UpdateProject' :: UpdateProject -> Maybe Int
defaultJobTimeoutMinutes} -> Maybe Int
defaultJobTimeoutMinutes) (\s :: UpdateProject
s@UpdateProject' {} Maybe Int
a -> UpdateProject
s {$sel:defaultJobTimeoutMinutes:UpdateProject' :: Maybe Int
defaultJobTimeoutMinutes = Maybe Int
a} :: UpdateProject)

-- | A string that represents the new name of the project that you are
-- updating.
updateProject_name :: Lens.Lens' UpdateProject (Prelude.Maybe Prelude.Text)
updateProject_name :: Lens' UpdateProject (Maybe Text)
updateProject_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProject' {Maybe Text
name :: Maybe Text
$sel:name:UpdateProject' :: UpdateProject -> Maybe Text
name} -> Maybe Text
name) (\s :: UpdateProject
s@UpdateProject' {} Maybe Text
a -> UpdateProject
s {$sel:name:UpdateProject' :: Maybe Text
name = Maybe Text
a} :: UpdateProject)

-- | The VPC security groups and subnets that are attached to a project.
updateProject_vpcConfig :: Lens.Lens' UpdateProject (Prelude.Maybe VpcConfig)
updateProject_vpcConfig :: Lens' UpdateProject (Maybe VpcConfig)
updateProject_vpcConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProject' {Maybe VpcConfig
vpcConfig :: Maybe VpcConfig
$sel:vpcConfig:UpdateProject' :: UpdateProject -> Maybe VpcConfig
vpcConfig} -> Maybe VpcConfig
vpcConfig) (\s :: UpdateProject
s@UpdateProject' {} Maybe VpcConfig
a -> UpdateProject
s {$sel:vpcConfig:UpdateProject' :: Maybe VpcConfig
vpcConfig = Maybe VpcConfig
a} :: UpdateProject)

-- | The Amazon Resource Name (ARN) of the project whose name to update.
updateProject_arn :: Lens.Lens' UpdateProject Prelude.Text
updateProject_arn :: Lens' UpdateProject Text
updateProject_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProject' {Text
arn :: Text
$sel:arn:UpdateProject' :: UpdateProject -> Text
arn} -> Text
arn) (\s :: UpdateProject
s@UpdateProject' {} Text
a -> UpdateProject
s {$sel:arn:UpdateProject' :: Text
arn = 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.postJSON (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 Project -> 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
"project")
            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 Int
Maybe Text
Maybe VpcConfig
Text
arn :: Text
vpcConfig :: Maybe VpcConfig
name :: Maybe Text
defaultJobTimeoutMinutes :: Maybe Int
$sel:arn:UpdateProject' :: UpdateProject -> Text
$sel:vpcConfig:UpdateProject' :: UpdateProject -> Maybe VpcConfig
$sel:name:UpdateProject' :: UpdateProject -> Maybe Text
$sel:defaultJobTimeoutMinutes:UpdateProject' :: UpdateProject -> Maybe Int
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
defaultJobTimeoutMinutes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe VpcConfig
vpcConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
arn

instance Prelude.NFData UpdateProject where
  rnf :: UpdateProject -> ()
rnf UpdateProject' {Maybe Int
Maybe Text
Maybe VpcConfig
Text
arn :: Text
vpcConfig :: Maybe VpcConfig
name :: Maybe Text
defaultJobTimeoutMinutes :: Maybe Int
$sel:arn:UpdateProject' :: UpdateProject -> Text
$sel:vpcConfig:UpdateProject' :: UpdateProject -> Maybe VpcConfig
$sel:name:UpdateProject' :: UpdateProject -> Maybe Text
$sel:defaultJobTimeoutMinutes:UpdateProject' :: UpdateProject -> Maybe Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
defaultJobTimeoutMinutes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe VpcConfig
vpcConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
arn

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
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"DeviceFarm_20150623.UpdateProject" ::
                          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 UpdateProject where
  toJSON :: UpdateProject -> Value
toJSON UpdateProject' {Maybe Int
Maybe Text
Maybe VpcConfig
Text
arn :: Text
vpcConfig :: Maybe VpcConfig
name :: Maybe Text
defaultJobTimeoutMinutes :: Maybe Int
$sel:arn:UpdateProject' :: UpdateProject -> Text
$sel:vpcConfig:UpdateProject' :: UpdateProject -> Maybe VpcConfig
$sel:name:UpdateProject' :: UpdateProject -> Maybe Text
$sel:defaultJobTimeoutMinutes:UpdateProject' :: UpdateProject -> Maybe Int
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"defaultJobTimeoutMinutes" 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 Int
defaultJobTimeoutMinutes,
            (Key
"name" 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
name,
            (Key
"vpcConfig" 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 VpcConfig
vpcConfig,
            forall a. a -> Maybe a
Prelude.Just (Key
"arn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
arn)
          ]
      )

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

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

-- | Represents the result of an update project request.
--
-- /See:/ 'newUpdateProjectResponse' smart constructor.
data UpdateProjectResponse = UpdateProjectResponse'
  { -- | The project to update.
    UpdateProjectResponse -> Maybe Project
project :: Prelude.Maybe Project,
    -- | 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:
--
-- 'project', 'updateProjectResponse_project' - The project to update.
--
-- 'httpStatus', 'updateProjectResponse_httpStatus' - The response's http status code.
newUpdateProjectResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateProjectResponse
newUpdateProjectResponse :: Int -> UpdateProjectResponse
newUpdateProjectResponse Int
pHttpStatus_ =
  UpdateProjectResponse'
    { $sel:project:UpdateProjectResponse' :: Maybe Project
project = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateProjectResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The project to update.
updateProjectResponse_project :: Lens.Lens' UpdateProjectResponse (Prelude.Maybe Project)
updateProjectResponse_project :: Lens' UpdateProjectResponse (Maybe Project)
updateProjectResponse_project = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProjectResponse' {Maybe Project
project :: Maybe Project
$sel:project:UpdateProjectResponse' :: UpdateProjectResponse -> Maybe Project
project} -> Maybe Project
project) (\s :: UpdateProjectResponse
s@UpdateProjectResponse' {} Maybe Project
a -> UpdateProjectResponse
s {$sel:project:UpdateProjectResponse' :: Maybe Project
project = Maybe Project
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 Project
httpStatus :: Int
project :: Maybe Project
$sel:httpStatus:UpdateProjectResponse' :: UpdateProjectResponse -> Int
$sel:project:UpdateProjectResponse' :: UpdateProjectResponse -> Maybe Project
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Project
project
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus