{-# 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.ServiceCatalog.CreatePortfolio
-- 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 portfolio.
--
-- A delegated admin is authorized to invoke this command.
module Amazonka.ServiceCatalog.CreatePortfolio
  ( -- * Creating a Request
    CreatePortfolio (..),
    newCreatePortfolio,

    -- * Request Lenses
    createPortfolio_acceptLanguage,
    createPortfolio_description,
    createPortfolio_tags,
    createPortfolio_displayName,
    createPortfolio_providerName,
    createPortfolio_idempotencyToken,

    -- * Destructuring the Response
    CreatePortfolioResponse (..),
    newCreatePortfolioResponse,

    -- * Response Lenses
    createPortfolioResponse_portfolioDetail,
    createPortfolioResponse_tags,
    createPortfolioResponse_httpStatus,
  )
where

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

-- | /See:/ 'newCreatePortfolio' smart constructor.
data CreatePortfolio = CreatePortfolio'
  { -- | The language code.
    --
    -- -   @en@ - English (default)
    --
    -- -   @jp@ - Japanese
    --
    -- -   @zh@ - Chinese
    CreatePortfolio -> Maybe Text
acceptLanguage :: Prelude.Maybe Prelude.Text,
    -- | The description of the portfolio.
    CreatePortfolio -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | One or more tags.
    CreatePortfolio -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The name to use for display purposes.
    CreatePortfolio -> Text
displayName :: Prelude.Text,
    -- | The name of the portfolio provider.
    CreatePortfolio -> Text
providerName :: Prelude.Text,
    -- | A unique identifier that you provide to ensure idempotency. If multiple
    -- requests differ only by the idempotency token, the same response is
    -- returned for each repeated request.
    CreatePortfolio -> Text
idempotencyToken :: Prelude.Text
  }
  deriving (CreatePortfolio -> CreatePortfolio -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreatePortfolio -> CreatePortfolio -> Bool
$c/= :: CreatePortfolio -> CreatePortfolio -> Bool
== :: CreatePortfolio -> CreatePortfolio -> Bool
$c== :: CreatePortfolio -> CreatePortfolio -> Bool
Prelude.Eq, ReadPrec [CreatePortfolio]
ReadPrec CreatePortfolio
Int -> ReadS CreatePortfolio
ReadS [CreatePortfolio]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreatePortfolio]
$creadListPrec :: ReadPrec [CreatePortfolio]
readPrec :: ReadPrec CreatePortfolio
$creadPrec :: ReadPrec CreatePortfolio
readList :: ReadS [CreatePortfolio]
$creadList :: ReadS [CreatePortfolio]
readsPrec :: Int -> ReadS CreatePortfolio
$creadsPrec :: Int -> ReadS CreatePortfolio
Prelude.Read, Int -> CreatePortfolio -> ShowS
[CreatePortfolio] -> ShowS
CreatePortfolio -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreatePortfolio] -> ShowS
$cshowList :: [CreatePortfolio] -> ShowS
show :: CreatePortfolio -> String
$cshow :: CreatePortfolio -> String
showsPrec :: Int -> CreatePortfolio -> ShowS
$cshowsPrec :: Int -> CreatePortfolio -> ShowS
Prelude.Show, forall x. Rep CreatePortfolio x -> CreatePortfolio
forall x. CreatePortfolio -> Rep CreatePortfolio x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreatePortfolio x -> CreatePortfolio
$cfrom :: forall x. CreatePortfolio -> Rep CreatePortfolio x
Prelude.Generic)

-- |
-- Create a value of 'CreatePortfolio' 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:
--
-- 'acceptLanguage', 'createPortfolio_acceptLanguage' - The language code.
--
-- -   @en@ - English (default)
--
-- -   @jp@ - Japanese
--
-- -   @zh@ - Chinese
--
-- 'description', 'createPortfolio_description' - The description of the portfolio.
--
-- 'tags', 'createPortfolio_tags' - One or more tags.
--
-- 'displayName', 'createPortfolio_displayName' - The name to use for display purposes.
--
-- 'providerName', 'createPortfolio_providerName' - The name of the portfolio provider.
--
-- 'idempotencyToken', 'createPortfolio_idempotencyToken' - A unique identifier that you provide to ensure idempotency. If multiple
-- requests differ only by the idempotency token, the same response is
-- returned for each repeated request.
newCreatePortfolio ::
  -- | 'displayName'
  Prelude.Text ->
  -- | 'providerName'
  Prelude.Text ->
  -- | 'idempotencyToken'
  Prelude.Text ->
  CreatePortfolio
newCreatePortfolio :: Text -> Text -> Text -> CreatePortfolio
newCreatePortfolio
  Text
pDisplayName_
  Text
pProviderName_
  Text
pIdempotencyToken_ =
    CreatePortfolio'
      { $sel:acceptLanguage:CreatePortfolio' :: Maybe Text
acceptLanguage = forall a. Maybe a
Prelude.Nothing,
        $sel:description:CreatePortfolio' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:CreatePortfolio' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:displayName:CreatePortfolio' :: Text
displayName = Text
pDisplayName_,
        $sel:providerName:CreatePortfolio' :: Text
providerName = Text
pProviderName_,
        $sel:idempotencyToken:CreatePortfolio' :: Text
idempotencyToken = Text
pIdempotencyToken_
      }

-- | The language code.
--
-- -   @en@ - English (default)
--
-- -   @jp@ - Japanese
--
-- -   @zh@ - Chinese
createPortfolio_acceptLanguage :: Lens.Lens' CreatePortfolio (Prelude.Maybe Prelude.Text)
createPortfolio_acceptLanguage :: Lens' CreatePortfolio (Maybe Text)
createPortfolio_acceptLanguage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePortfolio' {Maybe Text
acceptLanguage :: Maybe Text
$sel:acceptLanguage:CreatePortfolio' :: CreatePortfolio -> Maybe Text
acceptLanguage} -> Maybe Text
acceptLanguage) (\s :: CreatePortfolio
s@CreatePortfolio' {} Maybe Text
a -> CreatePortfolio
s {$sel:acceptLanguage:CreatePortfolio' :: Maybe Text
acceptLanguage = Maybe Text
a} :: CreatePortfolio)

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

-- | One or more tags.
createPortfolio_tags :: Lens.Lens' CreatePortfolio (Prelude.Maybe [Tag])
createPortfolio_tags :: Lens' CreatePortfolio (Maybe [Tag])
createPortfolio_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePortfolio' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreatePortfolio' :: CreatePortfolio -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreatePortfolio
s@CreatePortfolio' {} Maybe [Tag]
a -> CreatePortfolio
s {$sel:tags:CreatePortfolio' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreatePortfolio) 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 name to use for display purposes.
createPortfolio_displayName :: Lens.Lens' CreatePortfolio Prelude.Text
createPortfolio_displayName :: Lens' CreatePortfolio Text
createPortfolio_displayName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePortfolio' {Text
displayName :: Text
$sel:displayName:CreatePortfolio' :: CreatePortfolio -> Text
displayName} -> Text
displayName) (\s :: CreatePortfolio
s@CreatePortfolio' {} Text
a -> CreatePortfolio
s {$sel:displayName:CreatePortfolio' :: Text
displayName = Text
a} :: CreatePortfolio)

-- | The name of the portfolio provider.
createPortfolio_providerName :: Lens.Lens' CreatePortfolio Prelude.Text
createPortfolio_providerName :: Lens' CreatePortfolio Text
createPortfolio_providerName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePortfolio' {Text
providerName :: Text
$sel:providerName:CreatePortfolio' :: CreatePortfolio -> Text
providerName} -> Text
providerName) (\s :: CreatePortfolio
s@CreatePortfolio' {} Text
a -> CreatePortfolio
s {$sel:providerName:CreatePortfolio' :: Text
providerName = Text
a} :: CreatePortfolio)

-- | A unique identifier that you provide to ensure idempotency. If multiple
-- requests differ only by the idempotency token, the same response is
-- returned for each repeated request.
createPortfolio_idempotencyToken :: Lens.Lens' CreatePortfolio Prelude.Text
createPortfolio_idempotencyToken :: Lens' CreatePortfolio Text
createPortfolio_idempotencyToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePortfolio' {Text
idempotencyToken :: Text
$sel:idempotencyToken:CreatePortfolio' :: CreatePortfolio -> Text
idempotencyToken} -> Text
idempotencyToken) (\s :: CreatePortfolio
s@CreatePortfolio' {} Text
a -> CreatePortfolio
s {$sel:idempotencyToken:CreatePortfolio' :: Text
idempotencyToken = Text
a} :: CreatePortfolio)

instance Core.AWSRequest CreatePortfolio where
  type
    AWSResponse CreatePortfolio =
      CreatePortfolioResponse
  request :: (Service -> Service) -> CreatePortfolio -> Request CreatePortfolio
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 CreatePortfolio
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreatePortfolio)))
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 PortfolioDetail
-> Maybe [Tag] -> Int -> CreatePortfolioResponse
CreatePortfolioResponse'
            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
"PortfolioDetail")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Tags" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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 CreatePortfolio where
  hashWithSalt :: Int -> CreatePortfolio -> Int
hashWithSalt Int
_salt CreatePortfolio' {Maybe [Tag]
Maybe Text
Text
idempotencyToken :: Text
providerName :: Text
displayName :: Text
tags :: Maybe [Tag]
description :: Maybe Text
acceptLanguage :: Maybe Text
$sel:idempotencyToken:CreatePortfolio' :: CreatePortfolio -> Text
$sel:providerName:CreatePortfolio' :: CreatePortfolio -> Text
$sel:displayName:CreatePortfolio' :: CreatePortfolio -> Text
$sel:tags:CreatePortfolio' :: CreatePortfolio -> Maybe [Tag]
$sel:description:CreatePortfolio' :: CreatePortfolio -> Maybe Text
$sel:acceptLanguage:CreatePortfolio' :: CreatePortfolio -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
acceptLanguage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
displayName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
providerName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
idempotencyToken

instance Prelude.NFData CreatePortfolio where
  rnf :: CreatePortfolio -> ()
rnf CreatePortfolio' {Maybe [Tag]
Maybe Text
Text
idempotencyToken :: Text
providerName :: Text
displayName :: Text
tags :: Maybe [Tag]
description :: Maybe Text
acceptLanguage :: Maybe Text
$sel:idempotencyToken:CreatePortfolio' :: CreatePortfolio -> Text
$sel:providerName:CreatePortfolio' :: CreatePortfolio -> Text
$sel:displayName:CreatePortfolio' :: CreatePortfolio -> Text
$sel:tags:CreatePortfolio' :: CreatePortfolio -> Maybe [Tag]
$sel:description:CreatePortfolio' :: CreatePortfolio -> Maybe Text
$sel:acceptLanguage:CreatePortfolio' :: CreatePortfolio -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
acceptLanguage
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
displayName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
providerName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
idempotencyToken

instance Data.ToHeaders CreatePortfolio where
  toHeaders :: CreatePortfolio -> 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
"AWS242ServiceCatalogService.CreatePortfolio" ::
                          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 CreatePortfolio where
  toJSON :: CreatePortfolio -> Value
toJSON CreatePortfolio' {Maybe [Tag]
Maybe Text
Text
idempotencyToken :: Text
providerName :: Text
displayName :: Text
tags :: Maybe [Tag]
description :: Maybe Text
acceptLanguage :: Maybe Text
$sel:idempotencyToken:CreatePortfolio' :: CreatePortfolio -> Text
$sel:providerName:CreatePortfolio' :: CreatePortfolio -> Text
$sel:displayName:CreatePortfolio' :: CreatePortfolio -> Text
$sel:tags:CreatePortfolio' :: CreatePortfolio -> Maybe [Tag]
$sel:description:CreatePortfolio' :: CreatePortfolio -> Maybe Text
$sel:acceptLanguage:CreatePortfolio' :: CreatePortfolio -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AcceptLanguage" 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
acceptLanguage,
            (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 [Tag]
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"DisplayName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
displayName),
            forall a. a -> Maybe a
Prelude.Just (Key
"ProviderName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
providerName),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"IdempotencyToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
idempotencyToken)
          ]
      )

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

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

-- | /See:/ 'newCreatePortfolioResponse' smart constructor.
data CreatePortfolioResponse = CreatePortfolioResponse'
  { -- | Information about the portfolio.
    CreatePortfolioResponse -> Maybe PortfolioDetail
portfolioDetail :: Prelude.Maybe PortfolioDetail,
    -- | Information about the tags associated with the portfolio.
    CreatePortfolioResponse -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The response's http status code.
    CreatePortfolioResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreatePortfolioResponse -> CreatePortfolioResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreatePortfolioResponse -> CreatePortfolioResponse -> Bool
$c/= :: CreatePortfolioResponse -> CreatePortfolioResponse -> Bool
== :: CreatePortfolioResponse -> CreatePortfolioResponse -> Bool
$c== :: CreatePortfolioResponse -> CreatePortfolioResponse -> Bool
Prelude.Eq, ReadPrec [CreatePortfolioResponse]
ReadPrec CreatePortfolioResponse
Int -> ReadS CreatePortfolioResponse
ReadS [CreatePortfolioResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreatePortfolioResponse]
$creadListPrec :: ReadPrec [CreatePortfolioResponse]
readPrec :: ReadPrec CreatePortfolioResponse
$creadPrec :: ReadPrec CreatePortfolioResponse
readList :: ReadS [CreatePortfolioResponse]
$creadList :: ReadS [CreatePortfolioResponse]
readsPrec :: Int -> ReadS CreatePortfolioResponse
$creadsPrec :: Int -> ReadS CreatePortfolioResponse
Prelude.Read, Int -> CreatePortfolioResponse -> ShowS
[CreatePortfolioResponse] -> ShowS
CreatePortfolioResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreatePortfolioResponse] -> ShowS
$cshowList :: [CreatePortfolioResponse] -> ShowS
show :: CreatePortfolioResponse -> String
$cshow :: CreatePortfolioResponse -> String
showsPrec :: Int -> CreatePortfolioResponse -> ShowS
$cshowsPrec :: Int -> CreatePortfolioResponse -> ShowS
Prelude.Show, forall x. Rep CreatePortfolioResponse x -> CreatePortfolioResponse
forall x. CreatePortfolioResponse -> Rep CreatePortfolioResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreatePortfolioResponse x -> CreatePortfolioResponse
$cfrom :: forall x. CreatePortfolioResponse -> Rep CreatePortfolioResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreatePortfolioResponse' 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:
--
-- 'portfolioDetail', 'createPortfolioResponse_portfolioDetail' - Information about the portfolio.
--
-- 'tags', 'createPortfolioResponse_tags' - Information about the tags associated with the portfolio.
--
-- 'httpStatus', 'createPortfolioResponse_httpStatus' - The response's http status code.
newCreatePortfolioResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreatePortfolioResponse
newCreatePortfolioResponse :: Int -> CreatePortfolioResponse
newCreatePortfolioResponse Int
pHttpStatus_ =
  CreatePortfolioResponse'
    { $sel:portfolioDetail:CreatePortfolioResponse' :: Maybe PortfolioDetail
portfolioDetail =
        forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreatePortfolioResponse' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreatePortfolioResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the portfolio.
createPortfolioResponse_portfolioDetail :: Lens.Lens' CreatePortfolioResponse (Prelude.Maybe PortfolioDetail)
createPortfolioResponse_portfolioDetail :: Lens' CreatePortfolioResponse (Maybe PortfolioDetail)
createPortfolioResponse_portfolioDetail = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePortfolioResponse' {Maybe PortfolioDetail
portfolioDetail :: Maybe PortfolioDetail
$sel:portfolioDetail:CreatePortfolioResponse' :: CreatePortfolioResponse -> Maybe PortfolioDetail
portfolioDetail} -> Maybe PortfolioDetail
portfolioDetail) (\s :: CreatePortfolioResponse
s@CreatePortfolioResponse' {} Maybe PortfolioDetail
a -> CreatePortfolioResponse
s {$sel:portfolioDetail:CreatePortfolioResponse' :: Maybe PortfolioDetail
portfolioDetail = Maybe PortfolioDetail
a} :: CreatePortfolioResponse)

-- | Information about the tags associated with the portfolio.
createPortfolioResponse_tags :: Lens.Lens' CreatePortfolioResponse (Prelude.Maybe [Tag])
createPortfolioResponse_tags :: Lens' CreatePortfolioResponse (Maybe [Tag])
createPortfolioResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePortfolioResponse' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreatePortfolioResponse' :: CreatePortfolioResponse -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreatePortfolioResponse
s@CreatePortfolioResponse' {} Maybe [Tag]
a -> CreatePortfolioResponse
s {$sel:tags:CreatePortfolioResponse' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreatePortfolioResponse) 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 response's http status code.
createPortfolioResponse_httpStatus :: Lens.Lens' CreatePortfolioResponse Prelude.Int
createPortfolioResponse_httpStatus :: Lens' CreatePortfolioResponse Int
createPortfolioResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePortfolioResponse' {Int
httpStatus :: Int
$sel:httpStatus:CreatePortfolioResponse' :: CreatePortfolioResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: CreatePortfolioResponse
s@CreatePortfolioResponse' {} Int
a -> CreatePortfolioResponse
s {$sel:httpStatus:CreatePortfolioResponse' :: Int
httpStatus = Int
a} :: CreatePortfolioResponse)

instance Prelude.NFData CreatePortfolioResponse where
  rnf :: CreatePortfolioResponse -> ()
rnf CreatePortfolioResponse' {Int
Maybe [Tag]
Maybe PortfolioDetail
httpStatus :: Int
tags :: Maybe [Tag]
portfolioDetail :: Maybe PortfolioDetail
$sel:httpStatus:CreatePortfolioResponse' :: CreatePortfolioResponse -> Int
$sel:tags:CreatePortfolioResponse' :: CreatePortfolioResponse -> Maybe [Tag]
$sel:portfolioDetail:CreatePortfolioResponse' :: CreatePortfolioResponse -> Maybe PortfolioDetail
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe PortfolioDetail
portfolioDetail
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus