{-# 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.IoTSiteWise.CreateProject
-- 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 project in the specified portal.
--
-- Make sure that the project name and description don\'t contain
-- confidential information.
module Amazonka.IoTSiteWise.CreateProject
  ( -- * Creating a Request
    CreateProject (..),
    newCreateProject,

    -- * Request Lenses
    createProject_clientToken,
    createProject_projectDescription,
    createProject_tags,
    createProject_portalId,
    createProject_projectName,

    -- * Destructuring the Response
    CreateProjectResponse (..),
    newCreateProjectResponse,

    -- * Response Lenses
    createProjectResponse_httpStatus,
    createProjectResponse_projectId,
    createProjectResponse_projectArn,
  )
where

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

-- | /See:/ 'newCreateProject' smart constructor.
data CreateProject = CreateProject'
  { -- | A unique case-sensitive identifier that you can provide to ensure the
    -- idempotency of the request. Don\'t reuse this client token if a new
    -- idempotent request is required.
    CreateProject -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | A description for the project.
    CreateProject -> Maybe Text
projectDescription :: Prelude.Maybe Prelude.Text,
    -- | A list of key-value pairs that contain metadata for the project. For
    -- more information, see
    -- <https://docs.aws.amazon.com/iot-sitewise/latest/userguide/tag-resources.html Tagging your IoT SiteWise resources>
    -- in the /IoT SiteWise User Guide/.
    CreateProject -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The ID of the portal in which to create the project.
    CreateProject -> Text
portalId :: Prelude.Text,
    -- | A friendly name for the project.
    CreateProject -> Text
projectName :: Prelude.Text
  }
  deriving (CreateProject -> CreateProject -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateProject -> CreateProject -> Bool
$c/= :: CreateProject -> CreateProject -> Bool
== :: CreateProject -> CreateProject -> Bool
$c== :: CreateProject -> CreateProject -> Bool
Prelude.Eq, ReadPrec [CreateProject]
ReadPrec CreateProject
Int -> ReadS CreateProject
ReadS [CreateProject]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateProject]
$creadListPrec :: ReadPrec [CreateProject]
readPrec :: ReadPrec CreateProject
$creadPrec :: ReadPrec CreateProject
readList :: ReadS [CreateProject]
$creadList :: ReadS [CreateProject]
readsPrec :: Int -> ReadS CreateProject
$creadsPrec :: Int -> ReadS CreateProject
Prelude.Read, Int -> CreateProject -> ShowS
[CreateProject] -> ShowS
CreateProject -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateProject] -> ShowS
$cshowList :: [CreateProject] -> ShowS
show :: CreateProject -> String
$cshow :: CreateProject -> String
showsPrec :: Int -> CreateProject -> ShowS
$cshowsPrec :: Int -> CreateProject -> ShowS
Prelude.Show, forall x. Rep CreateProject x -> CreateProject
forall x. CreateProject -> Rep CreateProject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateProject x -> CreateProject
$cfrom :: forall x. CreateProject -> Rep CreateProject x
Prelude.Generic)

-- |
-- Create a value of 'CreateProject' 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:
--
-- 'clientToken', 'createProject_clientToken' - A unique case-sensitive identifier that you can provide to ensure the
-- idempotency of the request. Don\'t reuse this client token if a new
-- idempotent request is required.
--
-- 'projectDescription', 'createProject_projectDescription' - A description for the project.
--
-- 'tags', 'createProject_tags' - A list of key-value pairs that contain metadata for the project. For
-- more information, see
-- <https://docs.aws.amazon.com/iot-sitewise/latest/userguide/tag-resources.html Tagging your IoT SiteWise resources>
-- in the /IoT SiteWise User Guide/.
--
-- 'portalId', 'createProject_portalId' - The ID of the portal in which to create the project.
--
-- 'projectName', 'createProject_projectName' - A friendly name for the project.
newCreateProject ::
  -- | 'portalId'
  Prelude.Text ->
  -- | 'projectName'
  Prelude.Text ->
  CreateProject
newCreateProject :: Text -> Text -> CreateProject
newCreateProject Text
pPortalId_ Text
pProjectName_ =
  CreateProject'
    { $sel:clientToken:CreateProject' :: Maybe Text
clientToken = forall a. Maybe a
Prelude.Nothing,
      $sel:projectDescription:CreateProject' :: Maybe Text
projectDescription = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateProject' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:portalId:CreateProject' :: Text
portalId = Text
pPortalId_,
      $sel:projectName:CreateProject' :: Text
projectName = Text
pProjectName_
    }

-- | A unique case-sensitive identifier that you can provide to ensure the
-- idempotency of the request. Don\'t reuse this client token if a new
-- idempotent request is required.
createProject_clientToken :: Lens.Lens' CreateProject (Prelude.Maybe Prelude.Text)
createProject_clientToken :: Lens' CreateProject (Maybe Text)
createProject_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateProject' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:CreateProject' :: CreateProject -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: CreateProject
s@CreateProject' {} Maybe Text
a -> CreateProject
s {$sel:clientToken:CreateProject' :: Maybe Text
clientToken = Maybe Text
a} :: CreateProject)

-- | A description for the project.
createProject_projectDescription :: Lens.Lens' CreateProject (Prelude.Maybe Prelude.Text)
createProject_projectDescription :: Lens' CreateProject (Maybe Text)
createProject_projectDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateProject' {Maybe Text
projectDescription :: Maybe Text
$sel:projectDescription:CreateProject' :: CreateProject -> Maybe Text
projectDescription} -> Maybe Text
projectDescription) (\s :: CreateProject
s@CreateProject' {} Maybe Text
a -> CreateProject
s {$sel:projectDescription:CreateProject' :: Maybe Text
projectDescription = Maybe Text
a} :: CreateProject)

-- | A list of key-value pairs that contain metadata for the project. For
-- more information, see
-- <https://docs.aws.amazon.com/iot-sitewise/latest/userguide/tag-resources.html Tagging your IoT SiteWise resources>
-- in the /IoT SiteWise User Guide/.
createProject_tags :: Lens.Lens' CreateProject (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createProject_tags :: Lens' CreateProject (Maybe (HashMap Text Text))
createProject_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateProject' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateProject' :: CreateProject -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateProject
s@CreateProject' {} Maybe (HashMap Text Text)
a -> CreateProject
s {$sel:tags:CreateProject' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateProject) 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 portal in which to create the project.
createProject_portalId :: Lens.Lens' CreateProject Prelude.Text
createProject_portalId :: Lens' CreateProject Text
createProject_portalId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateProject' {Text
portalId :: Text
$sel:portalId:CreateProject' :: CreateProject -> Text
portalId} -> Text
portalId) (\s :: CreateProject
s@CreateProject' {} Text
a -> CreateProject
s {$sel:portalId:CreateProject' :: Text
portalId = Text
a} :: CreateProject)

-- | A friendly name for the project.
createProject_projectName :: Lens.Lens' CreateProject Prelude.Text
createProject_projectName :: Lens' CreateProject Text
createProject_projectName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateProject' {Text
projectName :: Text
$sel:projectName:CreateProject' :: CreateProject -> Text
projectName} -> Text
projectName) (\s :: CreateProject
s@CreateProject' {} Text
a -> CreateProject
s {$sel:projectName:CreateProject' :: Text
projectName = Text
a} :: CreateProject)

instance Core.AWSRequest CreateProject where
  type
    AWSResponse CreateProject =
      CreateProjectResponse
  request :: (Service -> Service) -> CreateProject -> Request CreateProject
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 CreateProject
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateProject)))
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 -> Text -> CreateProjectResponse
CreateProjectResponse'
            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
"projectId")
            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
"projectArn")
      )

instance Prelude.Hashable CreateProject where
  hashWithSalt :: Int -> CreateProject -> Int
hashWithSalt Int
_salt CreateProject' {Maybe Text
Maybe (HashMap Text Text)
Text
projectName :: Text
portalId :: Text
tags :: Maybe (HashMap Text Text)
projectDescription :: Maybe Text
clientToken :: Maybe Text
$sel:projectName:CreateProject' :: CreateProject -> Text
$sel:portalId:CreateProject' :: CreateProject -> Text
$sel:tags:CreateProject' :: CreateProject -> Maybe (HashMap Text Text)
$sel:projectDescription:CreateProject' :: CreateProject -> Maybe Text
$sel:clientToken:CreateProject' :: CreateProject -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
projectDescription
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
portalId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
projectName

instance Prelude.NFData CreateProject where
  rnf :: CreateProject -> ()
rnf CreateProject' {Maybe Text
Maybe (HashMap Text Text)
Text
projectName :: Text
portalId :: Text
tags :: Maybe (HashMap Text Text)
projectDescription :: Maybe Text
clientToken :: Maybe Text
$sel:projectName:CreateProject' :: CreateProject -> Text
$sel:portalId:CreateProject' :: CreateProject -> Text
$sel:tags:CreateProject' :: CreateProject -> Maybe (HashMap Text Text)
$sel:projectDescription:CreateProject' :: CreateProject -> Maybe Text
$sel:clientToken:CreateProject' :: CreateProject -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
projectDescription
      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
portalId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
projectName

instance Data.ToHeaders CreateProject where
  toHeaders :: CreateProject -> 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 CreateProject where
  toJSON :: CreateProject -> Value
toJSON CreateProject' {Maybe Text
Maybe (HashMap Text Text)
Text
projectName :: Text
portalId :: Text
tags :: Maybe (HashMap Text Text)
projectDescription :: Maybe Text
clientToken :: Maybe Text
$sel:projectName:CreateProject' :: CreateProject -> Text
$sel:portalId:CreateProject' :: CreateProject -> Text
$sel:tags:CreateProject' :: CreateProject -> Maybe (HashMap Text Text)
$sel:projectDescription:CreateProject' :: CreateProject -> Maybe Text
$sel:clientToken:CreateProject' :: CreateProject -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"clientToken" 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
clientToken,
            (Key
"projectDescription" 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
projectDescription,
            (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
"portalId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
portalId),
            forall a. a -> Maybe a
Prelude.Just (Key
"projectName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
projectName)
          ]
      )

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

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

-- | /See:/ 'newCreateProjectResponse' smart constructor.
data CreateProjectResponse = CreateProjectResponse'
  { -- | The response's http status code.
    CreateProjectResponse -> Int
httpStatus :: Prelude.Int,
    -- | The ID of the project.
    CreateProjectResponse -> Text
projectId :: Prelude.Text,
    -- | The
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html ARN>
    -- of the project, which has the following format.
    --
    -- @arn:${Partition}:iotsitewise:${Region}:${Account}:project\/${ProjectId}@
    CreateProjectResponse -> Text
projectArn :: Prelude.Text
  }
  deriving (CreateProjectResponse -> CreateProjectResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateProjectResponse -> CreateProjectResponse -> Bool
$c/= :: CreateProjectResponse -> CreateProjectResponse -> Bool
== :: CreateProjectResponse -> CreateProjectResponse -> Bool
$c== :: CreateProjectResponse -> CreateProjectResponse -> Bool
Prelude.Eq, ReadPrec [CreateProjectResponse]
ReadPrec CreateProjectResponse
Int -> ReadS CreateProjectResponse
ReadS [CreateProjectResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateProjectResponse]
$creadListPrec :: ReadPrec [CreateProjectResponse]
readPrec :: ReadPrec CreateProjectResponse
$creadPrec :: ReadPrec CreateProjectResponse
readList :: ReadS [CreateProjectResponse]
$creadList :: ReadS [CreateProjectResponse]
readsPrec :: Int -> ReadS CreateProjectResponse
$creadsPrec :: Int -> ReadS CreateProjectResponse
Prelude.Read, Int -> CreateProjectResponse -> ShowS
[CreateProjectResponse] -> ShowS
CreateProjectResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateProjectResponse] -> ShowS
$cshowList :: [CreateProjectResponse] -> ShowS
show :: CreateProjectResponse -> String
$cshow :: CreateProjectResponse -> String
showsPrec :: Int -> CreateProjectResponse -> ShowS
$cshowsPrec :: Int -> CreateProjectResponse -> ShowS
Prelude.Show, forall x. Rep CreateProjectResponse x -> CreateProjectResponse
forall x. CreateProjectResponse -> Rep CreateProjectResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateProjectResponse x -> CreateProjectResponse
$cfrom :: forall x. CreateProjectResponse -> Rep CreateProjectResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateProjectResponse' 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', 'createProjectResponse_httpStatus' - The response's http status code.
--
-- 'projectId', 'createProjectResponse_projectId' - The ID of the project.
--
-- 'projectArn', 'createProjectResponse_projectArn' - The
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html ARN>
-- of the project, which has the following format.
--
-- @arn:${Partition}:iotsitewise:${Region}:${Account}:project\/${ProjectId}@
newCreateProjectResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'projectId'
  Prelude.Text ->
  -- | 'projectArn'
  Prelude.Text ->
  CreateProjectResponse
newCreateProjectResponse :: Int -> Text -> Text -> CreateProjectResponse
newCreateProjectResponse
  Int
pHttpStatus_
  Text
pProjectId_
  Text
pProjectArn_ =
    CreateProjectResponse'
      { $sel:httpStatus:CreateProjectResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:projectId:CreateProjectResponse' :: Text
projectId = Text
pProjectId_,
        $sel:projectArn:CreateProjectResponse' :: Text
projectArn = Text
pProjectArn_
      }

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

-- | The ID of the project.
createProjectResponse_projectId :: Lens.Lens' CreateProjectResponse Prelude.Text
createProjectResponse_projectId :: Lens' CreateProjectResponse Text
createProjectResponse_projectId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateProjectResponse' {Text
projectId :: Text
$sel:projectId:CreateProjectResponse' :: CreateProjectResponse -> Text
projectId} -> Text
projectId) (\s :: CreateProjectResponse
s@CreateProjectResponse' {} Text
a -> CreateProjectResponse
s {$sel:projectId:CreateProjectResponse' :: Text
projectId = Text
a} :: CreateProjectResponse)

-- | The
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html ARN>
-- of the project, which has the following format.
--
-- @arn:${Partition}:iotsitewise:${Region}:${Account}:project\/${ProjectId}@
createProjectResponse_projectArn :: Lens.Lens' CreateProjectResponse Prelude.Text
createProjectResponse_projectArn :: Lens' CreateProjectResponse Text
createProjectResponse_projectArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateProjectResponse' {Text
projectArn :: Text
$sel:projectArn:CreateProjectResponse' :: CreateProjectResponse -> Text
projectArn} -> Text
projectArn) (\s :: CreateProjectResponse
s@CreateProjectResponse' {} Text
a -> CreateProjectResponse
s {$sel:projectArn:CreateProjectResponse' :: Text
projectArn = Text
a} :: CreateProjectResponse)

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