{-# 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.CreateWorkspace
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a workplace.
module Amazonka.IotTwinMaker.CreateWorkspace
  ( -- * Creating a Request
    CreateWorkspace (..),
    newCreateWorkspace,

    -- * Request Lenses
    createWorkspace_description,
    createWorkspace_tags,
    createWorkspace_workspaceId,
    createWorkspace_s3Location,
    createWorkspace_role,

    -- * Destructuring the Response
    CreateWorkspaceResponse (..),
    newCreateWorkspaceResponse,

    -- * Response Lenses
    createWorkspaceResponse_httpStatus,
    createWorkspaceResponse_arn,
    createWorkspaceResponse_creationDateTime,
  )
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:/ 'newCreateWorkspace' smart constructor.
data CreateWorkspace = CreateWorkspace'
  { -- | The description of the workspace.
    CreateWorkspace -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Metadata that you can use to manage the workspace
    CreateWorkspace -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The ID of the workspace.
    CreateWorkspace -> Text
workspaceId :: Prelude.Text,
    -- | The ARN of the S3 bucket where resources associated with the workspace
    -- are stored.
    CreateWorkspace -> Text
s3Location :: Prelude.Text,
    -- | The ARN of the execution role associated with the workspace.
    CreateWorkspace -> Text
role' :: Prelude.Text
  }
  deriving (CreateWorkspace -> CreateWorkspace -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateWorkspace -> CreateWorkspace -> Bool
$c/= :: CreateWorkspace -> CreateWorkspace -> Bool
== :: CreateWorkspace -> CreateWorkspace -> Bool
$c== :: CreateWorkspace -> CreateWorkspace -> Bool
Prelude.Eq, ReadPrec [CreateWorkspace]
ReadPrec CreateWorkspace
Int -> ReadS CreateWorkspace
ReadS [CreateWorkspace]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateWorkspace]
$creadListPrec :: ReadPrec [CreateWorkspace]
readPrec :: ReadPrec CreateWorkspace
$creadPrec :: ReadPrec CreateWorkspace
readList :: ReadS [CreateWorkspace]
$creadList :: ReadS [CreateWorkspace]
readsPrec :: Int -> ReadS CreateWorkspace
$creadsPrec :: Int -> ReadS CreateWorkspace
Prelude.Read, Int -> CreateWorkspace -> ShowS
[CreateWorkspace] -> ShowS
CreateWorkspace -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateWorkspace] -> ShowS
$cshowList :: [CreateWorkspace] -> ShowS
show :: CreateWorkspace -> String
$cshow :: CreateWorkspace -> String
showsPrec :: Int -> CreateWorkspace -> ShowS
$cshowsPrec :: Int -> CreateWorkspace -> ShowS
Prelude.Show, forall x. Rep CreateWorkspace x -> CreateWorkspace
forall x. CreateWorkspace -> Rep CreateWorkspace x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateWorkspace x -> CreateWorkspace
$cfrom :: forall x. CreateWorkspace -> Rep CreateWorkspace x
Prelude.Generic)

-- |
-- Create a value of 'CreateWorkspace' 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', 'createWorkspace_description' - The description of the workspace.
--
-- 'tags', 'createWorkspace_tags' - Metadata that you can use to manage the workspace
--
-- 'workspaceId', 'createWorkspace_workspaceId' - The ID of the workspace.
--
-- 's3Location', 'createWorkspace_s3Location' - The ARN of the S3 bucket where resources associated with the workspace
-- are stored.
--
-- 'role'', 'createWorkspace_role' - The ARN of the execution role associated with the workspace.
newCreateWorkspace ::
  -- | 'workspaceId'
  Prelude.Text ->
  -- | 's3Location'
  Prelude.Text ->
  -- | 'role''
  Prelude.Text ->
  CreateWorkspace
newCreateWorkspace :: Text -> Text -> Text -> CreateWorkspace
newCreateWorkspace Text
pWorkspaceId_ Text
pS3Location_ Text
pRole_ =
  CreateWorkspace'
    { $sel:description:CreateWorkspace' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateWorkspace' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:workspaceId:CreateWorkspace' :: Text
workspaceId = Text
pWorkspaceId_,
      $sel:s3Location:CreateWorkspace' :: Text
s3Location = Text
pS3Location_,
      $sel:role':CreateWorkspace' :: Text
role' = Text
pRole_
    }

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

-- | Metadata that you can use to manage the workspace
createWorkspace_tags :: Lens.Lens' CreateWorkspace (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createWorkspace_tags :: Lens' CreateWorkspace (Maybe (HashMap Text Text))
createWorkspace_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkspace' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateWorkspace' :: CreateWorkspace -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateWorkspace
s@CreateWorkspace' {} Maybe (HashMap Text Text)
a -> CreateWorkspace
s {$sel:tags:CreateWorkspace' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateWorkspace) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

-- | The ARN of the S3 bucket where resources associated with the workspace
-- are stored.
createWorkspace_s3Location :: Lens.Lens' CreateWorkspace Prelude.Text
createWorkspace_s3Location :: Lens' CreateWorkspace Text
createWorkspace_s3Location = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkspace' {Text
s3Location :: Text
$sel:s3Location:CreateWorkspace' :: CreateWorkspace -> Text
s3Location} -> Text
s3Location) (\s :: CreateWorkspace
s@CreateWorkspace' {} Text
a -> CreateWorkspace
s {$sel:s3Location:CreateWorkspace' :: Text
s3Location = Text
a} :: CreateWorkspace)

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

instance Core.AWSRequest CreateWorkspace where
  type
    AWSResponse CreateWorkspace =
      CreateWorkspaceResponse
  request :: (Service -> Service) -> CreateWorkspace -> Request CreateWorkspace
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 CreateWorkspace
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateWorkspace)))
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 -> Text -> POSIX -> CreateWorkspaceResponse
CreateWorkspaceResponse'
            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
"arn")
            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
"creationDateTime")
      )

instance Prelude.Hashable CreateWorkspace where
  hashWithSalt :: Int -> CreateWorkspace -> Int
hashWithSalt Int
_salt CreateWorkspace' {Maybe Text
Maybe (HashMap Text Text)
Text
role' :: Text
s3Location :: Text
workspaceId :: Text
tags :: Maybe (HashMap Text Text)
description :: Maybe Text
$sel:role':CreateWorkspace' :: CreateWorkspace -> Text
$sel:s3Location:CreateWorkspace' :: CreateWorkspace -> Text
$sel:workspaceId:CreateWorkspace' :: CreateWorkspace -> Text
$sel:tags:CreateWorkspace' :: CreateWorkspace -> Maybe (HashMap Text Text)
$sel:description:CreateWorkspace' :: CreateWorkspace -> 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 (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
workspaceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
s3Location
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
role'

instance Prelude.NFData CreateWorkspace where
  rnf :: CreateWorkspace -> ()
rnf CreateWorkspace' {Maybe Text
Maybe (HashMap Text Text)
Text
role' :: Text
s3Location :: Text
workspaceId :: Text
tags :: Maybe (HashMap Text Text)
description :: Maybe Text
$sel:role':CreateWorkspace' :: CreateWorkspace -> Text
$sel:s3Location:CreateWorkspace' :: CreateWorkspace -> Text
$sel:workspaceId:CreateWorkspace' :: CreateWorkspace -> Text
$sel:tags:CreateWorkspace' :: CreateWorkspace -> Maybe (HashMap Text Text)
$sel:description:CreateWorkspace' :: CreateWorkspace -> 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 (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
workspaceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
s3Location
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
role'

instance Data.ToHeaders CreateWorkspace where
  toHeaders :: CreateWorkspace -> 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 CreateWorkspace where
  toJSON :: CreateWorkspace -> Value
toJSON CreateWorkspace' {Maybe Text
Maybe (HashMap Text Text)
Text
role' :: Text
s3Location :: Text
workspaceId :: Text
tags :: Maybe (HashMap Text Text)
description :: Maybe Text
$sel:role':CreateWorkspace' :: CreateWorkspace -> Text
$sel:s3Location:CreateWorkspace' :: CreateWorkspace -> Text
$sel:workspaceId:CreateWorkspace' :: CreateWorkspace -> Text
$sel:tags:CreateWorkspace' :: CreateWorkspace -> Maybe (HashMap Text Text)
$sel:description:CreateWorkspace' :: CreateWorkspace -> 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
"tags" 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 (HashMap Text Text)
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"s3Location" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
s3Location),
            forall a. a -> Maybe a
Prelude.Just (Key
"role" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
role')
          ]
      )

instance Data.ToPath CreateWorkspace where
  toPath :: CreateWorkspace -> ByteString
toPath CreateWorkspace' {Maybe Text
Maybe (HashMap Text Text)
Text
role' :: Text
s3Location :: Text
workspaceId :: Text
tags :: Maybe (HashMap Text Text)
description :: Maybe Text
$sel:role':CreateWorkspace' :: CreateWorkspace -> Text
$sel:s3Location:CreateWorkspace' :: CreateWorkspace -> Text
$sel:workspaceId:CreateWorkspace' :: CreateWorkspace -> Text
$sel:tags:CreateWorkspace' :: CreateWorkspace -> Maybe (HashMap Text Text)
$sel:description:CreateWorkspace' :: CreateWorkspace -> 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 CreateWorkspace where
  toQuery :: CreateWorkspace -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

-- |
-- Create a value of 'CreateWorkspaceResponse' 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', 'createWorkspaceResponse_httpStatus' - The response's http status code.
--
-- 'arn', 'createWorkspaceResponse_arn' - The ARN of the workspace.
--
-- 'creationDateTime', 'createWorkspaceResponse_creationDateTime' - The date and time when the workspace was created.
newCreateWorkspaceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'arn'
  Prelude.Text ->
  -- | 'creationDateTime'
  Prelude.UTCTime ->
  CreateWorkspaceResponse
newCreateWorkspaceResponse :: Int -> Text -> UTCTime -> CreateWorkspaceResponse
newCreateWorkspaceResponse
  Int
pHttpStatus_
  Text
pArn_
  UTCTime
pCreationDateTime_ =
    CreateWorkspaceResponse'
      { $sel:httpStatus:CreateWorkspaceResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:arn:CreateWorkspaceResponse' :: Text
arn = Text
pArn_,
        $sel:creationDateTime:CreateWorkspaceResponse' :: POSIX
creationDateTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreationDateTime_
      }

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

-- | The ARN of the workspace.
createWorkspaceResponse_arn :: Lens.Lens' CreateWorkspaceResponse Prelude.Text
createWorkspaceResponse_arn :: Lens' CreateWorkspaceResponse Text
createWorkspaceResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkspaceResponse' {Text
arn :: Text
$sel:arn:CreateWorkspaceResponse' :: CreateWorkspaceResponse -> Text
arn} -> Text
arn) (\s :: CreateWorkspaceResponse
s@CreateWorkspaceResponse' {} Text
a -> CreateWorkspaceResponse
s {$sel:arn:CreateWorkspaceResponse' :: Text
arn = Text
a} :: CreateWorkspaceResponse)

-- | The date and time when the workspace was created.
createWorkspaceResponse_creationDateTime :: Lens.Lens' CreateWorkspaceResponse Prelude.UTCTime
createWorkspaceResponse_creationDateTime :: Lens' CreateWorkspaceResponse UTCTime
createWorkspaceResponse_creationDateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkspaceResponse' {POSIX
creationDateTime :: POSIX
$sel:creationDateTime:CreateWorkspaceResponse' :: CreateWorkspaceResponse -> POSIX
creationDateTime} -> POSIX
creationDateTime) (\s :: CreateWorkspaceResponse
s@CreateWorkspaceResponse' {} POSIX
a -> CreateWorkspaceResponse
s {$sel:creationDateTime:CreateWorkspaceResponse' :: POSIX
creationDateTime = POSIX
a} :: CreateWorkspaceResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

instance Prelude.NFData CreateWorkspaceResponse where
  rnf :: CreateWorkspaceResponse -> ()
rnf CreateWorkspaceResponse' {Int
Text
POSIX
creationDateTime :: POSIX
arn :: Text
httpStatus :: Int
$sel:creationDateTime:CreateWorkspaceResponse' :: CreateWorkspaceResponse -> POSIX
$sel:arn:CreateWorkspaceResponse' :: CreateWorkspaceResponse -> Text
$sel:httpStatus:CreateWorkspaceResponse' :: CreateWorkspaceResponse -> 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 Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
creationDateTime