{-# 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.IotTwinMaker.UpdateWorkspace
-- 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 workspace.
module Amazonka.IotTwinMaker.UpdateWorkspace
  ( -- * Creating a Request
    UpdateWorkspace (..),
    newUpdateWorkspace,

    -- * Request Lenses
    updateWorkspace_description,
    updateWorkspace_role,
    updateWorkspace_workspaceId,

    -- * Destructuring the Response
    UpdateWorkspaceResponse (..),
    newUpdateWorkspaceResponse,

    -- * Response Lenses
    updateWorkspaceResponse_httpStatus,
    updateWorkspaceResponse_updateDateTime,
  )
where

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

-- | /See:/ 'newUpdateWorkspace' smart constructor.
data UpdateWorkspace = UpdateWorkspace'
  { -- | The description of the workspace.
    UpdateWorkspace -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The ARN of the execution role associated with the workspace.
    UpdateWorkspace -> Maybe Text
role' :: Prelude.Maybe Prelude.Text,
    -- | The ID of the workspace.
    UpdateWorkspace -> Text
workspaceId :: Prelude.Text
  }
  deriving (UpdateWorkspace -> UpdateWorkspace -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateWorkspace -> UpdateWorkspace -> Bool
$c/= :: UpdateWorkspace -> UpdateWorkspace -> Bool
== :: UpdateWorkspace -> UpdateWorkspace -> Bool
$c== :: UpdateWorkspace -> UpdateWorkspace -> Bool
Prelude.Eq, ReadPrec [UpdateWorkspace]
ReadPrec UpdateWorkspace
Int -> ReadS UpdateWorkspace
ReadS [UpdateWorkspace]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateWorkspace]
$creadListPrec :: ReadPrec [UpdateWorkspace]
readPrec :: ReadPrec UpdateWorkspace
$creadPrec :: ReadPrec UpdateWorkspace
readList :: ReadS [UpdateWorkspace]
$creadList :: ReadS [UpdateWorkspace]
readsPrec :: Int -> ReadS UpdateWorkspace
$creadsPrec :: Int -> ReadS UpdateWorkspace
Prelude.Read, Int -> UpdateWorkspace -> ShowS
[UpdateWorkspace] -> ShowS
UpdateWorkspace -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateWorkspace] -> ShowS
$cshowList :: [UpdateWorkspace] -> ShowS
show :: UpdateWorkspace -> String
$cshow :: UpdateWorkspace -> String
showsPrec :: Int -> UpdateWorkspace -> ShowS
$cshowsPrec :: Int -> UpdateWorkspace -> ShowS
Prelude.Show, forall x. Rep UpdateWorkspace x -> UpdateWorkspace
forall x. UpdateWorkspace -> Rep UpdateWorkspace x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateWorkspace x -> UpdateWorkspace
$cfrom :: forall x. UpdateWorkspace -> Rep UpdateWorkspace x
Prelude.Generic)

-- |
-- Create a value of 'UpdateWorkspace' 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:
--
-- 'description', 'updateWorkspace_description' - The description of the workspace.
--
-- 'role'', 'updateWorkspace_role' - The ARN of the execution role associated with the workspace.
--
-- 'workspaceId', 'updateWorkspace_workspaceId' - The ID of the workspace.
newUpdateWorkspace ::
  -- | 'workspaceId'
  Prelude.Text ->
  UpdateWorkspace
newUpdateWorkspace :: Text -> UpdateWorkspace
newUpdateWorkspace Text
pWorkspaceId_ =
  UpdateWorkspace'
    { $sel:description:UpdateWorkspace' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:role':UpdateWorkspace' :: Maybe Text
role' = forall a. Maybe a
Prelude.Nothing,
      $sel:workspaceId:UpdateWorkspace' :: Text
workspaceId = Text
pWorkspaceId_
    }

-- | The description of the workspace.
updateWorkspace_description :: Lens.Lens' UpdateWorkspace (Prelude.Maybe Prelude.Text)
updateWorkspace_description :: Lens' UpdateWorkspace (Maybe Text)
updateWorkspace_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkspace' {Maybe Text
description :: Maybe Text
$sel:description:UpdateWorkspace' :: UpdateWorkspace -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateWorkspace
s@UpdateWorkspace' {} Maybe Text
a -> UpdateWorkspace
s {$sel:description:UpdateWorkspace' :: Maybe Text
description = Maybe Text
a} :: UpdateWorkspace)

-- | The ARN of the execution role associated with the workspace.
updateWorkspace_role :: Lens.Lens' UpdateWorkspace (Prelude.Maybe Prelude.Text)
updateWorkspace_role :: Lens' UpdateWorkspace (Maybe Text)
updateWorkspace_role = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkspace' {Maybe Text
role' :: Maybe Text
$sel:role':UpdateWorkspace' :: UpdateWorkspace -> Maybe Text
role'} -> Maybe Text
role') (\s :: UpdateWorkspace
s@UpdateWorkspace' {} Maybe Text
a -> UpdateWorkspace
s {$sel:role':UpdateWorkspace' :: Maybe Text
role' = Maybe Text
a} :: UpdateWorkspace)

-- | The ID of the workspace.
updateWorkspace_workspaceId :: Lens.Lens' UpdateWorkspace Prelude.Text
updateWorkspace_workspaceId :: Lens' UpdateWorkspace Text
updateWorkspace_workspaceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkspace' {Text
workspaceId :: Text
$sel:workspaceId:UpdateWorkspace' :: UpdateWorkspace -> Text
workspaceId} -> Text
workspaceId) (\s :: UpdateWorkspace
s@UpdateWorkspace' {} Text
a -> UpdateWorkspace
s {$sel:workspaceId:UpdateWorkspace' :: Text
workspaceId = Text
a} :: UpdateWorkspace)

instance Core.AWSRequest UpdateWorkspace where
  type
    AWSResponse UpdateWorkspace =
      UpdateWorkspaceResponse
  request :: (Service -> Service) -> UpdateWorkspace -> Request UpdateWorkspace
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 UpdateWorkspace
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateWorkspace)))
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 -> POSIX -> UpdateWorkspaceResponse
UpdateWorkspaceResponse'
            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
"updateDateTime")
      )

instance Prelude.Hashable UpdateWorkspace where
  hashWithSalt :: Int -> UpdateWorkspace -> Int
hashWithSalt Int
_salt UpdateWorkspace' {Maybe Text
Text
workspaceId :: Text
role' :: Maybe Text
description :: Maybe Text
$sel:workspaceId:UpdateWorkspace' :: UpdateWorkspace -> Text
$sel:role':UpdateWorkspace' :: UpdateWorkspace -> Maybe Text
$sel:description:UpdateWorkspace' :: UpdateWorkspace -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
role'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
workspaceId

instance Prelude.NFData UpdateWorkspace where
  rnf :: UpdateWorkspace -> ()
rnf UpdateWorkspace' {Maybe Text
Text
workspaceId :: Text
role' :: Maybe Text
description :: Maybe Text
$sel:workspaceId:UpdateWorkspace' :: UpdateWorkspace -> Text
$sel:role':UpdateWorkspace' :: UpdateWorkspace -> Maybe Text
$sel:description:UpdateWorkspace' :: UpdateWorkspace -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
role'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
workspaceId

instance Data.ToHeaders UpdateWorkspace where
  toHeaders :: UpdateWorkspace -> 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 UpdateWorkspace where
  toJSON :: UpdateWorkspace -> Value
toJSON UpdateWorkspace' {Maybe Text
Text
workspaceId :: Text
role' :: Maybe Text
description :: Maybe Text
$sel:workspaceId:UpdateWorkspace' :: UpdateWorkspace -> Text
$sel:role':UpdateWorkspace' :: UpdateWorkspace -> Maybe Text
$sel:description:UpdateWorkspace' :: UpdateWorkspace -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"description" 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
description,
            (Key
"role" 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
role'
          ]
      )

instance Data.ToPath UpdateWorkspace where
  toPath :: UpdateWorkspace -> ByteString
toPath UpdateWorkspace' {Maybe Text
Text
workspaceId :: Text
role' :: Maybe Text
description :: Maybe Text
$sel:workspaceId:UpdateWorkspace' :: UpdateWorkspace -> Text
$sel:role':UpdateWorkspace' :: UpdateWorkspace -> Maybe Text
$sel:description:UpdateWorkspace' :: UpdateWorkspace -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/workspaces/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
workspaceId]

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

-- | /See:/ 'newUpdateWorkspaceResponse' smart constructor.
data UpdateWorkspaceResponse = UpdateWorkspaceResponse'
  { -- | The response's http status code.
    UpdateWorkspaceResponse -> Int
httpStatus :: Prelude.Int,
    -- | The date and time of the current update.
    UpdateWorkspaceResponse -> POSIX
updateDateTime :: Data.POSIX
  }
  deriving (UpdateWorkspaceResponse -> UpdateWorkspaceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateWorkspaceResponse -> UpdateWorkspaceResponse -> Bool
$c/= :: UpdateWorkspaceResponse -> UpdateWorkspaceResponse -> Bool
== :: UpdateWorkspaceResponse -> UpdateWorkspaceResponse -> Bool
$c== :: UpdateWorkspaceResponse -> UpdateWorkspaceResponse -> Bool
Prelude.Eq, ReadPrec [UpdateWorkspaceResponse]
ReadPrec UpdateWorkspaceResponse
Int -> ReadS UpdateWorkspaceResponse
ReadS [UpdateWorkspaceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateWorkspaceResponse]
$creadListPrec :: ReadPrec [UpdateWorkspaceResponse]
readPrec :: ReadPrec UpdateWorkspaceResponse
$creadPrec :: ReadPrec UpdateWorkspaceResponse
readList :: ReadS [UpdateWorkspaceResponse]
$creadList :: ReadS [UpdateWorkspaceResponse]
readsPrec :: Int -> ReadS UpdateWorkspaceResponse
$creadsPrec :: Int -> ReadS UpdateWorkspaceResponse
Prelude.Read, Int -> UpdateWorkspaceResponse -> ShowS
[UpdateWorkspaceResponse] -> ShowS
UpdateWorkspaceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateWorkspaceResponse] -> ShowS
$cshowList :: [UpdateWorkspaceResponse] -> ShowS
show :: UpdateWorkspaceResponse -> String
$cshow :: UpdateWorkspaceResponse -> String
showsPrec :: Int -> UpdateWorkspaceResponse -> ShowS
$cshowsPrec :: Int -> UpdateWorkspaceResponse -> ShowS
Prelude.Show, forall x. Rep UpdateWorkspaceResponse x -> UpdateWorkspaceResponse
forall x. UpdateWorkspaceResponse -> Rep UpdateWorkspaceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateWorkspaceResponse x -> UpdateWorkspaceResponse
$cfrom :: forall x. UpdateWorkspaceResponse -> Rep UpdateWorkspaceResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateWorkspaceResponse' 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', 'updateWorkspaceResponse_httpStatus' - The response's http status code.
--
-- 'updateDateTime', 'updateWorkspaceResponse_updateDateTime' - The date and time of the current update.
newUpdateWorkspaceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'updateDateTime'
  Prelude.UTCTime ->
  UpdateWorkspaceResponse
newUpdateWorkspaceResponse :: Int -> UTCTime -> UpdateWorkspaceResponse
newUpdateWorkspaceResponse
  Int
pHttpStatus_
  UTCTime
pUpdateDateTime_ =
    UpdateWorkspaceResponse'
      { $sel:httpStatus:UpdateWorkspaceResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:updateDateTime:UpdateWorkspaceResponse' :: POSIX
updateDateTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pUpdateDateTime_
      }

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

-- | The date and time of the current update.
updateWorkspaceResponse_updateDateTime :: Lens.Lens' UpdateWorkspaceResponse Prelude.UTCTime
updateWorkspaceResponse_updateDateTime :: Lens' UpdateWorkspaceResponse UTCTime
updateWorkspaceResponse_updateDateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkspaceResponse' {POSIX
updateDateTime :: POSIX
$sel:updateDateTime:UpdateWorkspaceResponse' :: UpdateWorkspaceResponse -> POSIX
updateDateTime} -> POSIX
updateDateTime) (\s :: UpdateWorkspaceResponse
s@UpdateWorkspaceResponse' {} POSIX
a -> UpdateWorkspaceResponse
s {$sel:updateDateTime:UpdateWorkspaceResponse' :: POSIX
updateDateTime = POSIX
a} :: UpdateWorkspaceResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

instance Prelude.NFData UpdateWorkspaceResponse where
  rnf :: UpdateWorkspaceResponse -> ()
rnf UpdateWorkspaceResponse' {Int
POSIX
updateDateTime :: POSIX
httpStatus :: Int
$sel:updateDateTime:UpdateWorkspaceResponse' :: UpdateWorkspaceResponse -> POSIX
$sel:httpStatus:UpdateWorkspaceResponse' :: UpdateWorkspaceResponse -> 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 POSIX
updateDateTime