{-# 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.MigrationHubReFactorSpaces.CreateApplication
-- 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 an Amazon Web Services Migration Hub Refactor Spaces
-- application. The account that owns the environment also owns the
-- applications created inside the environment, regardless of the account
-- that creates the application. Refactor Spaces provisions an Amazon API
-- Gateway, API Gateway VPC link, and Network Load Balancer for the
-- application proxy inside your account.
module Amazonka.MigrationHubReFactorSpaces.CreateApplication
  ( -- * Creating a Request
    CreateApplication (..),
    newCreateApplication,

    -- * Request Lenses
    createApplication_apiGatewayProxy,
    createApplication_clientToken,
    createApplication_tags,
    createApplication_environmentIdentifier,
    createApplication_name,
    createApplication_proxyType,
    createApplication_vpcId,

    -- * Destructuring the Response
    CreateApplicationResponse (..),
    newCreateApplicationResponse,

    -- * Response Lenses
    createApplicationResponse_apiGatewayProxy,
    createApplicationResponse_applicationId,
    createApplicationResponse_arn,
    createApplicationResponse_createdByAccountId,
    createApplicationResponse_createdTime,
    createApplicationResponse_environmentId,
    createApplicationResponse_lastUpdatedTime,
    createApplicationResponse_name,
    createApplicationResponse_ownerAccountId,
    createApplicationResponse_proxyType,
    createApplicationResponse_state,
    createApplicationResponse_tags,
    createApplicationResponse_vpcId,
    createApplicationResponse_httpStatus,
  )
where

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

-- | /See:/ 'newCreateApplication' smart constructor.
data CreateApplication = CreateApplication'
  { -- | A wrapper object holding the API Gateway endpoint type and stage name
    -- for the proxy.
    CreateApplication -> Maybe ApiGatewayProxyInput
apiGatewayProxy :: Prelude.Maybe ApiGatewayProxyInput,
    -- | A unique, case-sensitive identifier that you provide to ensure the
    -- idempotency of the request.
    CreateApplication -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | The tags to assign to the application. A tag is a label that you assign
    -- to an Amazon Web Services resource. Each tag consists of a key-value
    -- pair.
    CreateApplication -> Maybe (Sensitive (HashMap Text Text))
tags :: Prelude.Maybe (Data.Sensitive (Prelude.HashMap Prelude.Text Prelude.Text)),
    -- | The unique identifier of the environment.
    CreateApplication -> Text
environmentIdentifier :: Prelude.Text,
    -- | The name to use for the application.
    CreateApplication -> Text
name :: Prelude.Text,
    -- | The proxy type of the proxy created within the application.
    CreateApplication -> ProxyType
proxyType :: ProxyType,
    -- | The ID of the virtual private cloud (VPC).
    CreateApplication -> Text
vpcId :: Prelude.Text
  }
  deriving (CreateApplication -> CreateApplication -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateApplication -> CreateApplication -> Bool
$c/= :: CreateApplication -> CreateApplication -> Bool
== :: CreateApplication -> CreateApplication -> Bool
$c== :: CreateApplication -> CreateApplication -> Bool
Prelude.Eq, Int -> CreateApplication -> ShowS
[CreateApplication] -> ShowS
CreateApplication -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateApplication] -> ShowS
$cshowList :: [CreateApplication] -> ShowS
show :: CreateApplication -> String
$cshow :: CreateApplication -> String
showsPrec :: Int -> CreateApplication -> ShowS
$cshowsPrec :: Int -> CreateApplication -> ShowS
Prelude.Show, forall x. Rep CreateApplication x -> CreateApplication
forall x. CreateApplication -> Rep CreateApplication x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateApplication x -> CreateApplication
$cfrom :: forall x. CreateApplication -> Rep CreateApplication x
Prelude.Generic)

-- |
-- Create a value of 'CreateApplication' 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:
--
-- 'apiGatewayProxy', 'createApplication_apiGatewayProxy' - A wrapper object holding the API Gateway endpoint type and stage name
-- for the proxy.
--
-- 'clientToken', 'createApplication_clientToken' - A unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the request.
--
-- 'tags', 'createApplication_tags' - The tags to assign to the application. A tag is a label that you assign
-- to an Amazon Web Services resource. Each tag consists of a key-value
-- pair.
--
-- 'environmentIdentifier', 'createApplication_environmentIdentifier' - The unique identifier of the environment.
--
-- 'name', 'createApplication_name' - The name to use for the application.
--
-- 'proxyType', 'createApplication_proxyType' - The proxy type of the proxy created within the application.
--
-- 'vpcId', 'createApplication_vpcId' - The ID of the virtual private cloud (VPC).
newCreateApplication ::
  -- | 'environmentIdentifier'
  Prelude.Text ->
  -- | 'name'
  Prelude.Text ->
  -- | 'proxyType'
  ProxyType ->
  -- | 'vpcId'
  Prelude.Text ->
  CreateApplication
newCreateApplication :: Text -> Text -> ProxyType -> Text -> CreateApplication
newCreateApplication
  Text
pEnvironmentIdentifier_
  Text
pName_
  ProxyType
pProxyType_
  Text
pVpcId_ =
    CreateApplication'
      { $sel:apiGatewayProxy:CreateApplication' :: Maybe ApiGatewayProxyInput
apiGatewayProxy =
          forall a. Maybe a
Prelude.Nothing,
        $sel:clientToken:CreateApplication' :: Maybe Text
clientToken = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:CreateApplication' :: Maybe (Sensitive (HashMap Text Text))
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:environmentIdentifier:CreateApplication' :: Text
environmentIdentifier = Text
pEnvironmentIdentifier_,
        $sel:name:CreateApplication' :: Text
name = Text
pName_,
        $sel:proxyType:CreateApplication' :: ProxyType
proxyType = ProxyType
pProxyType_,
        $sel:vpcId:CreateApplication' :: Text
vpcId = Text
pVpcId_
      }

-- | A wrapper object holding the API Gateway endpoint type and stage name
-- for the proxy.
createApplication_apiGatewayProxy :: Lens.Lens' CreateApplication (Prelude.Maybe ApiGatewayProxyInput)
createApplication_apiGatewayProxy :: Lens' CreateApplication (Maybe ApiGatewayProxyInput)
createApplication_apiGatewayProxy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplication' {Maybe ApiGatewayProxyInput
apiGatewayProxy :: Maybe ApiGatewayProxyInput
$sel:apiGatewayProxy:CreateApplication' :: CreateApplication -> Maybe ApiGatewayProxyInput
apiGatewayProxy} -> Maybe ApiGatewayProxyInput
apiGatewayProxy) (\s :: CreateApplication
s@CreateApplication' {} Maybe ApiGatewayProxyInput
a -> CreateApplication
s {$sel:apiGatewayProxy:CreateApplication' :: Maybe ApiGatewayProxyInput
apiGatewayProxy = Maybe ApiGatewayProxyInput
a} :: CreateApplication)

-- | A unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the request.
createApplication_clientToken :: Lens.Lens' CreateApplication (Prelude.Maybe Prelude.Text)
createApplication_clientToken :: Lens' CreateApplication (Maybe Text)
createApplication_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplication' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:CreateApplication' :: CreateApplication -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: CreateApplication
s@CreateApplication' {} Maybe Text
a -> CreateApplication
s {$sel:clientToken:CreateApplication' :: Maybe Text
clientToken = Maybe Text
a} :: CreateApplication)

-- | The tags to assign to the application. A tag is a label that you assign
-- to an Amazon Web Services resource. Each tag consists of a key-value
-- pair.
createApplication_tags :: Lens.Lens' CreateApplication (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createApplication_tags :: Lens' CreateApplication (Maybe (HashMap Text Text))
createApplication_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplication' {Maybe (Sensitive (HashMap Text Text))
tags :: Maybe (Sensitive (HashMap Text Text))
$sel:tags:CreateApplication' :: CreateApplication -> Maybe (Sensitive (HashMap Text Text))
tags} -> Maybe (Sensitive (HashMap Text Text))
tags) (\s :: CreateApplication
s@CreateApplication' {} Maybe (Sensitive (HashMap Text Text))
a -> CreateApplication
s {$sel:tags:CreateApplication' :: Maybe (Sensitive (HashMap Text Text))
tags = Maybe (Sensitive (HashMap Text Text))
a} :: CreateApplication) 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 a. Iso' (Sensitive a) a
Data._Sensitive forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced)

-- | The unique identifier of the environment.
createApplication_environmentIdentifier :: Lens.Lens' CreateApplication Prelude.Text
createApplication_environmentIdentifier :: Lens' CreateApplication Text
createApplication_environmentIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplication' {Text
environmentIdentifier :: Text
$sel:environmentIdentifier:CreateApplication' :: CreateApplication -> Text
environmentIdentifier} -> Text
environmentIdentifier) (\s :: CreateApplication
s@CreateApplication' {} Text
a -> CreateApplication
s {$sel:environmentIdentifier:CreateApplication' :: Text
environmentIdentifier = Text
a} :: CreateApplication)

-- | The name to use for the application.
createApplication_name :: Lens.Lens' CreateApplication Prelude.Text
createApplication_name :: Lens' CreateApplication Text
createApplication_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplication' {Text
name :: Text
$sel:name:CreateApplication' :: CreateApplication -> Text
name} -> Text
name) (\s :: CreateApplication
s@CreateApplication' {} Text
a -> CreateApplication
s {$sel:name:CreateApplication' :: Text
name = Text
a} :: CreateApplication)

-- | The proxy type of the proxy created within the application.
createApplication_proxyType :: Lens.Lens' CreateApplication ProxyType
createApplication_proxyType :: Lens' CreateApplication ProxyType
createApplication_proxyType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplication' {ProxyType
proxyType :: ProxyType
$sel:proxyType:CreateApplication' :: CreateApplication -> ProxyType
proxyType} -> ProxyType
proxyType) (\s :: CreateApplication
s@CreateApplication' {} ProxyType
a -> CreateApplication
s {$sel:proxyType:CreateApplication' :: ProxyType
proxyType = ProxyType
a} :: CreateApplication)

-- | The ID of the virtual private cloud (VPC).
createApplication_vpcId :: Lens.Lens' CreateApplication Prelude.Text
createApplication_vpcId :: Lens' CreateApplication Text
createApplication_vpcId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplication' {Text
vpcId :: Text
$sel:vpcId:CreateApplication' :: CreateApplication -> Text
vpcId} -> Text
vpcId) (\s :: CreateApplication
s@CreateApplication' {} Text
a -> CreateApplication
s {$sel:vpcId:CreateApplication' :: Text
vpcId = Text
a} :: CreateApplication)

instance Core.AWSRequest CreateApplication where
  type
    AWSResponse CreateApplication =
      CreateApplicationResponse
  request :: (Service -> Service)
-> CreateApplication -> Request CreateApplication
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 CreateApplication
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateApplication)))
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 ApiGatewayProxyInput
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe ProxyType
-> Maybe ApplicationState
-> Maybe (Sensitive (HashMap Text Text))
-> Maybe Text
-> Int
-> CreateApplicationResponse
CreateApplicationResponse'
            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
"ApiGatewayProxy")
            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
"ApplicationId")
            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
"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 (Maybe a)
Data..?> Key
"CreatedByAccountId")
            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
"CreatedTime")
            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
"EnvironmentId")
            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
"LastUpdatedTime")
            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
"Name")
            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
"OwnerAccountId")
            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
"ProxyType")
            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
"State")
            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"VpcId")
            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 CreateApplication where
  hashWithSalt :: Int -> CreateApplication -> Int
hashWithSalt Int
_salt CreateApplication' {Maybe Text
Maybe (Sensitive (HashMap Text Text))
Maybe ApiGatewayProxyInput
Text
ProxyType
vpcId :: Text
proxyType :: ProxyType
name :: Text
environmentIdentifier :: Text
tags :: Maybe (Sensitive (HashMap Text Text))
clientToken :: Maybe Text
apiGatewayProxy :: Maybe ApiGatewayProxyInput
$sel:vpcId:CreateApplication' :: CreateApplication -> Text
$sel:proxyType:CreateApplication' :: CreateApplication -> ProxyType
$sel:name:CreateApplication' :: CreateApplication -> Text
$sel:environmentIdentifier:CreateApplication' :: CreateApplication -> Text
$sel:tags:CreateApplication' :: CreateApplication -> Maybe (Sensitive (HashMap Text Text))
$sel:clientToken:CreateApplication' :: CreateApplication -> Maybe Text
$sel:apiGatewayProxy:CreateApplication' :: CreateApplication -> Maybe ApiGatewayProxyInput
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ApiGatewayProxyInput
apiGatewayProxy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive (HashMap Text Text))
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
environmentIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ProxyType
proxyType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
vpcId

instance Prelude.NFData CreateApplication where
  rnf :: CreateApplication -> ()
rnf CreateApplication' {Maybe Text
Maybe (Sensitive (HashMap Text Text))
Maybe ApiGatewayProxyInput
Text
ProxyType
vpcId :: Text
proxyType :: ProxyType
name :: Text
environmentIdentifier :: Text
tags :: Maybe (Sensitive (HashMap Text Text))
clientToken :: Maybe Text
apiGatewayProxy :: Maybe ApiGatewayProxyInput
$sel:vpcId:CreateApplication' :: CreateApplication -> Text
$sel:proxyType:CreateApplication' :: CreateApplication -> ProxyType
$sel:name:CreateApplication' :: CreateApplication -> Text
$sel:environmentIdentifier:CreateApplication' :: CreateApplication -> Text
$sel:tags:CreateApplication' :: CreateApplication -> Maybe (Sensitive (HashMap Text Text))
$sel:clientToken:CreateApplication' :: CreateApplication -> Maybe Text
$sel:apiGatewayProxy:CreateApplication' :: CreateApplication -> Maybe ApiGatewayProxyInput
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ApiGatewayProxyInput
apiGatewayProxy
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 (Sensitive (HashMap Text Text))
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
environmentIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ProxyType
proxyType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
vpcId

instance Data.ToHeaders CreateApplication where
  toHeaders :: CreateApplication -> 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 CreateApplication where
  toJSON :: CreateApplication -> Value
toJSON CreateApplication' {Maybe Text
Maybe (Sensitive (HashMap Text Text))
Maybe ApiGatewayProxyInput
Text
ProxyType
vpcId :: Text
proxyType :: ProxyType
name :: Text
environmentIdentifier :: Text
tags :: Maybe (Sensitive (HashMap Text Text))
clientToken :: Maybe Text
apiGatewayProxy :: Maybe ApiGatewayProxyInput
$sel:vpcId:CreateApplication' :: CreateApplication -> Text
$sel:proxyType:CreateApplication' :: CreateApplication -> ProxyType
$sel:name:CreateApplication' :: CreateApplication -> Text
$sel:environmentIdentifier:CreateApplication' :: CreateApplication -> Text
$sel:tags:CreateApplication' :: CreateApplication -> Maybe (Sensitive (HashMap Text Text))
$sel:clientToken:CreateApplication' :: CreateApplication -> Maybe Text
$sel:apiGatewayProxy:CreateApplication' :: CreateApplication -> Maybe ApiGatewayProxyInput
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ApiGatewayProxy" 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 ApiGatewayProxyInput
apiGatewayProxy,
            (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
"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 (Sensitive (HashMap Text Text))
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name),
            forall a. a -> Maybe a
Prelude.Just (Key
"ProxyType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ProxyType
proxyType),
            forall a. a -> Maybe a
Prelude.Just (Key
"VpcId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
vpcId)
          ]
      )

instance Data.ToPath CreateApplication where
  toPath :: CreateApplication -> ByteString
toPath CreateApplication' {Maybe Text
Maybe (Sensitive (HashMap Text Text))
Maybe ApiGatewayProxyInput
Text
ProxyType
vpcId :: Text
proxyType :: ProxyType
name :: Text
environmentIdentifier :: Text
tags :: Maybe (Sensitive (HashMap Text Text))
clientToken :: Maybe Text
apiGatewayProxy :: Maybe ApiGatewayProxyInput
$sel:vpcId:CreateApplication' :: CreateApplication -> Text
$sel:proxyType:CreateApplication' :: CreateApplication -> ProxyType
$sel:name:CreateApplication' :: CreateApplication -> Text
$sel:environmentIdentifier:CreateApplication' :: CreateApplication -> Text
$sel:tags:CreateApplication' :: CreateApplication -> Maybe (Sensitive (HashMap Text Text))
$sel:clientToken:CreateApplication' :: CreateApplication -> Maybe Text
$sel:apiGatewayProxy:CreateApplication' :: CreateApplication -> Maybe ApiGatewayProxyInput
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/environments/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
environmentIdentifier,
        ByteString
"/applications"
      ]

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

-- | /See:/ 'newCreateApplicationResponse' smart constructor.
data CreateApplicationResponse = CreateApplicationResponse'
  { -- | A wrapper object holding the API Gateway endpoint type and stage name
    -- for the proxy.
    CreateApplicationResponse -> Maybe ApiGatewayProxyInput
apiGatewayProxy :: Prelude.Maybe ApiGatewayProxyInput,
    -- | The unique identifier of the application.
    CreateApplicationResponse -> Maybe Text
applicationId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the application. The format for this
    -- ARN is
    -- @arn:aws:refactor-spaces:@/@region@/@:@/@account-id@/@:@/@resource-type\/resource-id@/@ @.
    -- For more information about ARNs, see
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
    -- in the /Amazon Web Services General Reference/.
    CreateApplicationResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services account ID of application creator.
    CreateApplicationResponse -> Maybe Text
createdByAccountId :: Prelude.Maybe Prelude.Text,
    -- | A timestamp that indicates when the application is created.
    CreateApplicationResponse -> Maybe POSIX
createdTime :: Prelude.Maybe Data.POSIX,
    -- | The ID of the environment in which the application is created.
    CreateApplicationResponse -> Maybe Text
environmentId :: Prelude.Maybe Prelude.Text,
    -- | A timestamp that indicates when the application was last updated.
    CreateApplicationResponse -> Maybe POSIX
lastUpdatedTime :: Prelude.Maybe Data.POSIX,
    -- | The name of the application.
    CreateApplicationResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services account ID of the application owner (which is
    -- always the same as the environment owner account ID).
    CreateApplicationResponse -> Maybe Text
ownerAccountId :: Prelude.Maybe Prelude.Text,
    -- | The proxy type of the proxy created within the application.
    CreateApplicationResponse -> Maybe ProxyType
proxyType :: Prelude.Maybe ProxyType,
    -- | The current state of the application.
    CreateApplicationResponse -> Maybe ApplicationState
state :: Prelude.Maybe ApplicationState,
    -- | The tags assigned to the application. A tag is a label that you assign
    -- to an Amazon Web Services resource. Each tag consists of a key-value
    -- pair.
    CreateApplicationResponse -> Maybe (Sensitive (HashMap Text Text))
tags :: Prelude.Maybe (Data.Sensitive (Prelude.HashMap Prelude.Text Prelude.Text)),
    -- | The ID of the Amazon VPC.
    CreateApplicationResponse -> Maybe Text
vpcId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateApplicationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateApplicationResponse -> CreateApplicationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateApplicationResponse -> CreateApplicationResponse -> Bool
$c/= :: CreateApplicationResponse -> CreateApplicationResponse -> Bool
== :: CreateApplicationResponse -> CreateApplicationResponse -> Bool
$c== :: CreateApplicationResponse -> CreateApplicationResponse -> Bool
Prelude.Eq, Int -> CreateApplicationResponse -> ShowS
[CreateApplicationResponse] -> ShowS
CreateApplicationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateApplicationResponse] -> ShowS
$cshowList :: [CreateApplicationResponse] -> ShowS
show :: CreateApplicationResponse -> String
$cshow :: CreateApplicationResponse -> String
showsPrec :: Int -> CreateApplicationResponse -> ShowS
$cshowsPrec :: Int -> CreateApplicationResponse -> ShowS
Prelude.Show, forall x.
Rep CreateApplicationResponse x -> CreateApplicationResponse
forall x.
CreateApplicationResponse -> Rep CreateApplicationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateApplicationResponse x -> CreateApplicationResponse
$cfrom :: forall x.
CreateApplicationResponse -> Rep CreateApplicationResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateApplicationResponse' 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:
--
-- 'apiGatewayProxy', 'createApplicationResponse_apiGatewayProxy' - A wrapper object holding the API Gateway endpoint type and stage name
-- for the proxy.
--
-- 'applicationId', 'createApplicationResponse_applicationId' - The unique identifier of the application.
--
-- 'arn', 'createApplicationResponse_arn' - The Amazon Resource Name (ARN) of the application. The format for this
-- ARN is
-- @arn:aws:refactor-spaces:@/@region@/@:@/@account-id@/@:@/@resource-type\/resource-id@/@ @.
-- For more information about ARNs, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- in the /Amazon Web Services General Reference/.
--
-- 'createdByAccountId', 'createApplicationResponse_createdByAccountId' - The Amazon Web Services account ID of application creator.
--
-- 'createdTime', 'createApplicationResponse_createdTime' - A timestamp that indicates when the application is created.
--
-- 'environmentId', 'createApplicationResponse_environmentId' - The ID of the environment in which the application is created.
--
-- 'lastUpdatedTime', 'createApplicationResponse_lastUpdatedTime' - A timestamp that indicates when the application was last updated.
--
-- 'name', 'createApplicationResponse_name' - The name of the application.
--
-- 'ownerAccountId', 'createApplicationResponse_ownerAccountId' - The Amazon Web Services account ID of the application owner (which is
-- always the same as the environment owner account ID).
--
-- 'proxyType', 'createApplicationResponse_proxyType' - The proxy type of the proxy created within the application.
--
-- 'state', 'createApplicationResponse_state' - The current state of the application.
--
-- 'tags', 'createApplicationResponse_tags' - The tags assigned to the application. A tag is a label that you assign
-- to an Amazon Web Services resource. Each tag consists of a key-value
-- pair.
--
-- 'vpcId', 'createApplicationResponse_vpcId' - The ID of the Amazon VPC.
--
-- 'httpStatus', 'createApplicationResponse_httpStatus' - The response's http status code.
newCreateApplicationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateApplicationResponse
newCreateApplicationResponse :: Int -> CreateApplicationResponse
newCreateApplicationResponse Int
pHttpStatus_ =
  CreateApplicationResponse'
    { $sel:apiGatewayProxy:CreateApplicationResponse' :: Maybe ApiGatewayProxyInput
apiGatewayProxy =
        forall a. Maybe a
Prelude.Nothing,
      $sel:applicationId:CreateApplicationResponse' :: Maybe Text
applicationId = forall a. Maybe a
Prelude.Nothing,
      $sel:arn:CreateApplicationResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:createdByAccountId:CreateApplicationResponse' :: Maybe Text
createdByAccountId = forall a. Maybe a
Prelude.Nothing,
      $sel:createdTime:CreateApplicationResponse' :: Maybe POSIX
createdTime = forall a. Maybe a
Prelude.Nothing,
      $sel:environmentId:CreateApplicationResponse' :: Maybe Text
environmentId = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdatedTime:CreateApplicationResponse' :: Maybe POSIX
lastUpdatedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:name:CreateApplicationResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:ownerAccountId:CreateApplicationResponse' :: Maybe Text
ownerAccountId = forall a. Maybe a
Prelude.Nothing,
      $sel:proxyType:CreateApplicationResponse' :: Maybe ProxyType
proxyType = forall a. Maybe a
Prelude.Nothing,
      $sel:state:CreateApplicationResponse' :: Maybe ApplicationState
state = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateApplicationResponse' :: Maybe (Sensitive (HashMap Text Text))
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcId:CreateApplicationResponse' :: Maybe Text
vpcId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateApplicationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A wrapper object holding the API Gateway endpoint type and stage name
-- for the proxy.
createApplicationResponse_apiGatewayProxy :: Lens.Lens' CreateApplicationResponse (Prelude.Maybe ApiGatewayProxyInput)
createApplicationResponse_apiGatewayProxy :: Lens' CreateApplicationResponse (Maybe ApiGatewayProxyInput)
createApplicationResponse_apiGatewayProxy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplicationResponse' {Maybe ApiGatewayProxyInput
apiGatewayProxy :: Maybe ApiGatewayProxyInput
$sel:apiGatewayProxy:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe ApiGatewayProxyInput
apiGatewayProxy} -> Maybe ApiGatewayProxyInput
apiGatewayProxy) (\s :: CreateApplicationResponse
s@CreateApplicationResponse' {} Maybe ApiGatewayProxyInput
a -> CreateApplicationResponse
s {$sel:apiGatewayProxy:CreateApplicationResponse' :: Maybe ApiGatewayProxyInput
apiGatewayProxy = Maybe ApiGatewayProxyInput
a} :: CreateApplicationResponse)

-- | The unique identifier of the application.
createApplicationResponse_applicationId :: Lens.Lens' CreateApplicationResponse (Prelude.Maybe Prelude.Text)
createApplicationResponse_applicationId :: Lens' CreateApplicationResponse (Maybe Text)
createApplicationResponse_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplicationResponse' {Maybe Text
applicationId :: Maybe Text
$sel:applicationId:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe Text
applicationId} -> Maybe Text
applicationId) (\s :: CreateApplicationResponse
s@CreateApplicationResponse' {} Maybe Text
a -> CreateApplicationResponse
s {$sel:applicationId:CreateApplicationResponse' :: Maybe Text
applicationId = Maybe Text
a} :: CreateApplicationResponse)

-- | The Amazon Resource Name (ARN) of the application. The format for this
-- ARN is
-- @arn:aws:refactor-spaces:@/@region@/@:@/@account-id@/@:@/@resource-type\/resource-id@/@ @.
-- For more information about ARNs, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- in the /Amazon Web Services General Reference/.
createApplicationResponse_arn :: Lens.Lens' CreateApplicationResponse (Prelude.Maybe Prelude.Text)
createApplicationResponse_arn :: Lens' CreateApplicationResponse (Maybe Text)
createApplicationResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplicationResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: CreateApplicationResponse
s@CreateApplicationResponse' {} Maybe Text
a -> CreateApplicationResponse
s {$sel:arn:CreateApplicationResponse' :: Maybe Text
arn = Maybe Text
a} :: CreateApplicationResponse)

-- | The Amazon Web Services account ID of application creator.
createApplicationResponse_createdByAccountId :: Lens.Lens' CreateApplicationResponse (Prelude.Maybe Prelude.Text)
createApplicationResponse_createdByAccountId :: Lens' CreateApplicationResponse (Maybe Text)
createApplicationResponse_createdByAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplicationResponse' {Maybe Text
createdByAccountId :: Maybe Text
$sel:createdByAccountId:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe Text
createdByAccountId} -> Maybe Text
createdByAccountId) (\s :: CreateApplicationResponse
s@CreateApplicationResponse' {} Maybe Text
a -> CreateApplicationResponse
s {$sel:createdByAccountId:CreateApplicationResponse' :: Maybe Text
createdByAccountId = Maybe Text
a} :: CreateApplicationResponse)

-- | A timestamp that indicates when the application is created.
createApplicationResponse_createdTime :: Lens.Lens' CreateApplicationResponse (Prelude.Maybe Prelude.UTCTime)
createApplicationResponse_createdTime :: Lens' CreateApplicationResponse (Maybe UTCTime)
createApplicationResponse_createdTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplicationResponse' {Maybe POSIX
createdTime :: Maybe POSIX
$sel:createdTime:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe POSIX
createdTime} -> Maybe POSIX
createdTime) (\s :: CreateApplicationResponse
s@CreateApplicationResponse' {} Maybe POSIX
a -> CreateApplicationResponse
s {$sel:createdTime:CreateApplicationResponse' :: Maybe POSIX
createdTime = Maybe POSIX
a} :: CreateApplicationResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The ID of the environment in which the application is created.
createApplicationResponse_environmentId :: Lens.Lens' CreateApplicationResponse (Prelude.Maybe Prelude.Text)
createApplicationResponse_environmentId :: Lens' CreateApplicationResponse (Maybe Text)
createApplicationResponse_environmentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplicationResponse' {Maybe Text
environmentId :: Maybe Text
$sel:environmentId:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe Text
environmentId} -> Maybe Text
environmentId) (\s :: CreateApplicationResponse
s@CreateApplicationResponse' {} Maybe Text
a -> CreateApplicationResponse
s {$sel:environmentId:CreateApplicationResponse' :: Maybe Text
environmentId = Maybe Text
a} :: CreateApplicationResponse)

-- | A timestamp that indicates when the application was last updated.
createApplicationResponse_lastUpdatedTime :: Lens.Lens' CreateApplicationResponse (Prelude.Maybe Prelude.UTCTime)
createApplicationResponse_lastUpdatedTime :: Lens' CreateApplicationResponse (Maybe UTCTime)
createApplicationResponse_lastUpdatedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplicationResponse' {Maybe POSIX
lastUpdatedTime :: Maybe POSIX
$sel:lastUpdatedTime:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe POSIX
lastUpdatedTime} -> Maybe POSIX
lastUpdatedTime) (\s :: CreateApplicationResponse
s@CreateApplicationResponse' {} Maybe POSIX
a -> CreateApplicationResponse
s {$sel:lastUpdatedTime:CreateApplicationResponse' :: Maybe POSIX
lastUpdatedTime = Maybe POSIX
a} :: CreateApplicationResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The name of the application.
createApplicationResponse_name :: Lens.Lens' CreateApplicationResponse (Prelude.Maybe Prelude.Text)
createApplicationResponse_name :: Lens' CreateApplicationResponse (Maybe Text)
createApplicationResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplicationResponse' {Maybe Text
name :: Maybe Text
$sel:name:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: CreateApplicationResponse
s@CreateApplicationResponse' {} Maybe Text
a -> CreateApplicationResponse
s {$sel:name:CreateApplicationResponse' :: Maybe Text
name = Maybe Text
a} :: CreateApplicationResponse)

-- | The Amazon Web Services account ID of the application owner (which is
-- always the same as the environment owner account ID).
createApplicationResponse_ownerAccountId :: Lens.Lens' CreateApplicationResponse (Prelude.Maybe Prelude.Text)
createApplicationResponse_ownerAccountId :: Lens' CreateApplicationResponse (Maybe Text)
createApplicationResponse_ownerAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplicationResponse' {Maybe Text
ownerAccountId :: Maybe Text
$sel:ownerAccountId:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe Text
ownerAccountId} -> Maybe Text
ownerAccountId) (\s :: CreateApplicationResponse
s@CreateApplicationResponse' {} Maybe Text
a -> CreateApplicationResponse
s {$sel:ownerAccountId:CreateApplicationResponse' :: Maybe Text
ownerAccountId = Maybe Text
a} :: CreateApplicationResponse)

-- | The proxy type of the proxy created within the application.
createApplicationResponse_proxyType :: Lens.Lens' CreateApplicationResponse (Prelude.Maybe ProxyType)
createApplicationResponse_proxyType :: Lens' CreateApplicationResponse (Maybe ProxyType)
createApplicationResponse_proxyType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplicationResponse' {Maybe ProxyType
proxyType :: Maybe ProxyType
$sel:proxyType:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe ProxyType
proxyType} -> Maybe ProxyType
proxyType) (\s :: CreateApplicationResponse
s@CreateApplicationResponse' {} Maybe ProxyType
a -> CreateApplicationResponse
s {$sel:proxyType:CreateApplicationResponse' :: Maybe ProxyType
proxyType = Maybe ProxyType
a} :: CreateApplicationResponse)

-- | The current state of the application.
createApplicationResponse_state :: Lens.Lens' CreateApplicationResponse (Prelude.Maybe ApplicationState)
createApplicationResponse_state :: Lens' CreateApplicationResponse (Maybe ApplicationState)
createApplicationResponse_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplicationResponse' {Maybe ApplicationState
state :: Maybe ApplicationState
$sel:state:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe ApplicationState
state} -> Maybe ApplicationState
state) (\s :: CreateApplicationResponse
s@CreateApplicationResponse' {} Maybe ApplicationState
a -> CreateApplicationResponse
s {$sel:state:CreateApplicationResponse' :: Maybe ApplicationState
state = Maybe ApplicationState
a} :: CreateApplicationResponse)

-- | The tags assigned to the application. A tag is a label that you assign
-- to an Amazon Web Services resource. Each tag consists of a key-value
-- pair.
createApplicationResponse_tags :: Lens.Lens' CreateApplicationResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createApplicationResponse_tags :: Lens' CreateApplicationResponse (Maybe (HashMap Text Text))
createApplicationResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplicationResponse' {Maybe (Sensitive (HashMap Text Text))
tags :: Maybe (Sensitive (HashMap Text Text))
$sel:tags:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe (Sensitive (HashMap Text Text))
tags} -> Maybe (Sensitive (HashMap Text Text))
tags) (\s :: CreateApplicationResponse
s@CreateApplicationResponse' {} Maybe (Sensitive (HashMap Text Text))
a -> CreateApplicationResponse
s {$sel:tags:CreateApplicationResponse' :: Maybe (Sensitive (HashMap Text Text))
tags = Maybe (Sensitive (HashMap Text Text))
a} :: CreateApplicationResponse) 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 a. Iso' (Sensitive a) a
Data._Sensitive forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced)

-- | The ID of the Amazon VPC.
createApplicationResponse_vpcId :: Lens.Lens' CreateApplicationResponse (Prelude.Maybe Prelude.Text)
createApplicationResponse_vpcId :: Lens' CreateApplicationResponse (Maybe Text)
createApplicationResponse_vpcId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplicationResponse' {Maybe Text
vpcId :: Maybe Text
$sel:vpcId:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe Text
vpcId} -> Maybe Text
vpcId) (\s :: CreateApplicationResponse
s@CreateApplicationResponse' {} Maybe Text
a -> CreateApplicationResponse
s {$sel:vpcId:CreateApplicationResponse' :: Maybe Text
vpcId = Maybe Text
a} :: CreateApplicationResponse)

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

instance Prelude.NFData CreateApplicationResponse where
  rnf :: CreateApplicationResponse -> ()
rnf CreateApplicationResponse' {Int
Maybe Text
Maybe (Sensitive (HashMap Text Text))
Maybe POSIX
Maybe ApiGatewayProxyInput
Maybe ApplicationState
Maybe ProxyType
httpStatus :: Int
vpcId :: Maybe Text
tags :: Maybe (Sensitive (HashMap Text Text))
state :: Maybe ApplicationState
proxyType :: Maybe ProxyType
ownerAccountId :: Maybe Text
name :: Maybe Text
lastUpdatedTime :: Maybe POSIX
environmentId :: Maybe Text
createdTime :: Maybe POSIX
createdByAccountId :: Maybe Text
arn :: Maybe Text
applicationId :: Maybe Text
apiGatewayProxy :: Maybe ApiGatewayProxyInput
$sel:httpStatus:CreateApplicationResponse' :: CreateApplicationResponse -> Int
$sel:vpcId:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe Text
$sel:tags:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe (Sensitive (HashMap Text Text))
$sel:state:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe ApplicationState
$sel:proxyType:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe ProxyType
$sel:ownerAccountId:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe Text
$sel:name:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe Text
$sel:lastUpdatedTime:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe POSIX
$sel:environmentId:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe Text
$sel:createdTime:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe POSIX
$sel:createdByAccountId:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe Text
$sel:arn:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe Text
$sel:applicationId:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe Text
$sel:apiGatewayProxy:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe ApiGatewayProxyInput
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ApiGatewayProxyInput
apiGatewayProxy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
applicationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
createdByAccountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
environmentId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastUpdatedTime
      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 Text
ownerAccountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ProxyType
proxyType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ApplicationState
state
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive (HashMap Text Text))
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
vpcId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus