{-# 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.GetApplication
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets an Amazon Web Services Migration Hub Refactor Spaces application.
module Amazonka.MigrationHubReFactorSpaces.GetApplication
  ( -- * Creating a Request
    GetApplication (..),
    newGetApplication,

    -- * Request Lenses
    getApplication_applicationIdentifier,
    getApplication_environmentIdentifier,

    -- * Destructuring the Response
    GetApplicationResponse (..),
    newGetApplicationResponse,

    -- * Response Lenses
    getApplicationResponse_apiGatewayProxy,
    getApplicationResponse_applicationId,
    getApplicationResponse_arn,
    getApplicationResponse_createdByAccountId,
    getApplicationResponse_createdTime,
    getApplicationResponse_environmentId,
    getApplicationResponse_error,
    getApplicationResponse_lastUpdatedTime,
    getApplicationResponse_name,
    getApplicationResponse_ownerAccountId,
    getApplicationResponse_proxyType,
    getApplicationResponse_state,
    getApplicationResponse_tags,
    getApplicationResponse_vpcId,
    getApplicationResponse_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:/ 'newGetApplication' smart constructor.
data GetApplication = GetApplication'
  { -- | The ID of the application.
    GetApplication -> Text
applicationIdentifier :: Prelude.Text,
    -- | The ID of the environment.
    GetApplication -> Text
environmentIdentifier :: Prelude.Text
  }
  deriving (GetApplication -> GetApplication -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetApplication -> GetApplication -> Bool
$c/= :: GetApplication -> GetApplication -> Bool
== :: GetApplication -> GetApplication -> Bool
$c== :: GetApplication -> GetApplication -> Bool
Prelude.Eq, ReadPrec [GetApplication]
ReadPrec GetApplication
Int -> ReadS GetApplication
ReadS [GetApplication]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetApplication]
$creadListPrec :: ReadPrec [GetApplication]
readPrec :: ReadPrec GetApplication
$creadPrec :: ReadPrec GetApplication
readList :: ReadS [GetApplication]
$creadList :: ReadS [GetApplication]
readsPrec :: Int -> ReadS GetApplication
$creadsPrec :: Int -> ReadS GetApplication
Prelude.Read, Int -> GetApplication -> ShowS
[GetApplication] -> ShowS
GetApplication -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetApplication] -> ShowS
$cshowList :: [GetApplication] -> ShowS
show :: GetApplication -> String
$cshow :: GetApplication -> String
showsPrec :: Int -> GetApplication -> ShowS
$cshowsPrec :: Int -> GetApplication -> ShowS
Prelude.Show, forall x. Rep GetApplication x -> GetApplication
forall x. GetApplication -> Rep GetApplication x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetApplication x -> GetApplication
$cfrom :: forall x. GetApplication -> Rep GetApplication x
Prelude.Generic)

-- |
-- Create a value of 'GetApplication' 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:
--
-- 'applicationIdentifier', 'getApplication_applicationIdentifier' - The ID of the application.
--
-- 'environmentIdentifier', 'getApplication_environmentIdentifier' - The ID of the environment.
newGetApplication ::
  -- | 'applicationIdentifier'
  Prelude.Text ->
  -- | 'environmentIdentifier'
  Prelude.Text ->
  GetApplication
newGetApplication :: Text -> Text -> GetApplication
newGetApplication
  Text
pApplicationIdentifier_
  Text
pEnvironmentIdentifier_ =
    GetApplication'
      { $sel:applicationIdentifier:GetApplication' :: Text
applicationIdentifier =
          Text
pApplicationIdentifier_,
        $sel:environmentIdentifier:GetApplication' :: Text
environmentIdentifier = Text
pEnvironmentIdentifier_
      }

-- | The ID of the application.
getApplication_applicationIdentifier :: Lens.Lens' GetApplication Prelude.Text
getApplication_applicationIdentifier :: Lens' GetApplication Text
getApplication_applicationIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetApplication' {Text
applicationIdentifier :: Text
$sel:applicationIdentifier:GetApplication' :: GetApplication -> Text
applicationIdentifier} -> Text
applicationIdentifier) (\s :: GetApplication
s@GetApplication' {} Text
a -> GetApplication
s {$sel:applicationIdentifier:GetApplication' :: Text
applicationIdentifier = Text
a} :: GetApplication)

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

instance Core.AWSRequest GetApplication where
  type
    AWSResponse GetApplication =
      GetApplicationResponse
  request :: (Service -> Service) -> GetApplication -> Request GetApplication
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetApplication
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetApplication)))
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 ApiGatewayProxyConfig
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe ErrorResponse
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe ProxyType
-> Maybe ApplicationState
-> Maybe (Sensitive (HashMap Text Text))
-> Maybe Text
-> Int
-> GetApplicationResponse
GetApplicationResponse'
            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
"Error")
            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 GetApplication where
  hashWithSalt :: Int -> GetApplication -> Int
hashWithSalt Int
_salt GetApplication' {Text
environmentIdentifier :: Text
applicationIdentifier :: Text
$sel:environmentIdentifier:GetApplication' :: GetApplication -> Text
$sel:applicationIdentifier:GetApplication' :: GetApplication -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
environmentIdentifier

instance Prelude.NFData GetApplication where
  rnf :: GetApplication -> ()
rnf GetApplication' {Text
environmentIdentifier :: Text
applicationIdentifier :: Text
$sel:environmentIdentifier:GetApplication' :: GetApplication -> Text
$sel:applicationIdentifier:GetApplication' :: GetApplication -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
applicationIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
environmentIdentifier

instance Data.ToHeaders GetApplication where
  toHeaders :: GetApplication -> 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.ToPath GetApplication where
  toPath :: GetApplication -> ByteString
toPath GetApplication' {Text
environmentIdentifier :: Text
applicationIdentifier :: Text
$sel:environmentIdentifier:GetApplication' :: GetApplication -> Text
$sel:applicationIdentifier:GetApplication' :: GetApplication -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/environments/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
environmentIdentifier,
        ByteString
"/applications/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationIdentifier
      ]

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

-- | /See:/ 'newGetApplicationResponse' smart constructor.
data GetApplicationResponse = GetApplicationResponse'
  { -- | The endpoint URL of the API Gateway proxy.
    GetApplicationResponse -> Maybe ApiGatewayProxyConfig
apiGatewayProxy :: Prelude.Maybe ApiGatewayProxyConfig,
    -- | The unique identifier of the application.
    GetApplicationResponse -> Maybe Text
applicationId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the application.
    GetApplicationResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services account ID of the application creator.
    GetApplicationResponse -> Maybe Text
createdByAccountId :: Prelude.Maybe Prelude.Text,
    -- | A timestamp that indicates when the application is created.
    GetApplicationResponse -> Maybe POSIX
createdTime :: Prelude.Maybe Data.POSIX,
    -- | The unique identifier of the environment.
    GetApplicationResponse -> Maybe Text
environmentId :: Prelude.Maybe Prelude.Text,
    -- | Any error associated with the application resource.
    GetApplicationResponse -> Maybe ErrorResponse
error :: Prelude.Maybe ErrorResponse,
    -- | A timestamp that indicates when the application was last updated.
    GetApplicationResponse -> Maybe POSIX
lastUpdatedTime :: Prelude.Maybe Data.POSIX,
    -- | The name of the application.
    GetApplicationResponse -> 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).
    GetApplicationResponse -> Maybe Text
ownerAccountId :: Prelude.Maybe Prelude.Text,
    -- | The proxy type of the proxy created within the application.
    GetApplicationResponse -> Maybe ProxyType
proxyType :: Prelude.Maybe ProxyType,
    -- | The current state of the application.
    GetApplicationResponse -> 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.
    GetApplicationResponse -> Maybe (Sensitive (HashMap Text Text))
tags :: Prelude.Maybe (Data.Sensitive (Prelude.HashMap Prelude.Text Prelude.Text)),
    -- | The ID of the virtual private cloud (VPC).
    GetApplicationResponse -> Maybe Text
vpcId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetApplicationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetApplicationResponse -> GetApplicationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetApplicationResponse -> GetApplicationResponse -> Bool
$c/= :: GetApplicationResponse -> GetApplicationResponse -> Bool
== :: GetApplicationResponse -> GetApplicationResponse -> Bool
$c== :: GetApplicationResponse -> GetApplicationResponse -> Bool
Prelude.Eq, Int -> GetApplicationResponse -> ShowS
[GetApplicationResponse] -> ShowS
GetApplicationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetApplicationResponse] -> ShowS
$cshowList :: [GetApplicationResponse] -> ShowS
show :: GetApplicationResponse -> String
$cshow :: GetApplicationResponse -> String
showsPrec :: Int -> GetApplicationResponse -> ShowS
$cshowsPrec :: Int -> GetApplicationResponse -> ShowS
Prelude.Show, forall x. Rep GetApplicationResponse x -> GetApplicationResponse
forall x. GetApplicationResponse -> Rep GetApplicationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetApplicationResponse x -> GetApplicationResponse
$cfrom :: forall x. GetApplicationResponse -> Rep GetApplicationResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetApplicationResponse' 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', 'getApplicationResponse_apiGatewayProxy' - The endpoint URL of the API Gateway proxy.
--
-- 'applicationId', 'getApplicationResponse_applicationId' - The unique identifier of the application.
--
-- 'arn', 'getApplicationResponse_arn' - The Amazon Resource Name (ARN) of the application.
--
-- 'createdByAccountId', 'getApplicationResponse_createdByAccountId' - The Amazon Web Services account ID of the application creator.
--
-- 'createdTime', 'getApplicationResponse_createdTime' - A timestamp that indicates when the application is created.
--
-- 'environmentId', 'getApplicationResponse_environmentId' - The unique identifier of the environment.
--
-- 'error', 'getApplicationResponse_error' - Any error associated with the application resource.
--
-- 'lastUpdatedTime', 'getApplicationResponse_lastUpdatedTime' - A timestamp that indicates when the application was last updated.
--
-- 'name', 'getApplicationResponse_name' - The name of the application.
--
-- 'ownerAccountId', 'getApplicationResponse_ownerAccountId' - The Amazon Web Services account ID of the application owner (which is
-- always the same as the environment owner account ID).
--
-- 'proxyType', 'getApplicationResponse_proxyType' - The proxy type of the proxy created within the application.
--
-- 'state', 'getApplicationResponse_state' - The current state of the application.
--
-- 'tags', 'getApplicationResponse_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', 'getApplicationResponse_vpcId' - The ID of the virtual private cloud (VPC).
--
-- 'httpStatus', 'getApplicationResponse_httpStatus' - The response's http status code.
newGetApplicationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetApplicationResponse
newGetApplicationResponse :: Int -> GetApplicationResponse
newGetApplicationResponse Int
pHttpStatus_ =
  GetApplicationResponse'
    { $sel:apiGatewayProxy:GetApplicationResponse' :: Maybe ApiGatewayProxyConfig
apiGatewayProxy =
        forall a. Maybe a
Prelude.Nothing,
      $sel:applicationId:GetApplicationResponse' :: Maybe Text
applicationId = forall a. Maybe a
Prelude.Nothing,
      $sel:arn:GetApplicationResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:createdByAccountId:GetApplicationResponse' :: Maybe Text
createdByAccountId = forall a. Maybe a
Prelude.Nothing,
      $sel:createdTime:GetApplicationResponse' :: Maybe POSIX
createdTime = forall a. Maybe a
Prelude.Nothing,
      $sel:environmentId:GetApplicationResponse' :: Maybe Text
environmentId = forall a. Maybe a
Prelude.Nothing,
      $sel:error:GetApplicationResponse' :: Maybe ErrorResponse
error = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdatedTime:GetApplicationResponse' :: Maybe POSIX
lastUpdatedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:name:GetApplicationResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:ownerAccountId:GetApplicationResponse' :: Maybe Text
ownerAccountId = forall a. Maybe a
Prelude.Nothing,
      $sel:proxyType:GetApplicationResponse' :: Maybe ProxyType
proxyType = forall a. Maybe a
Prelude.Nothing,
      $sel:state:GetApplicationResponse' :: Maybe ApplicationState
state = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:GetApplicationResponse' :: Maybe (Sensitive (HashMap Text Text))
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcId:GetApplicationResponse' :: Maybe Text
vpcId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetApplicationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The endpoint URL of the API Gateway proxy.
getApplicationResponse_apiGatewayProxy :: Lens.Lens' GetApplicationResponse (Prelude.Maybe ApiGatewayProxyConfig)
getApplicationResponse_apiGatewayProxy :: Lens' GetApplicationResponse (Maybe ApiGatewayProxyConfig)
getApplicationResponse_apiGatewayProxy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetApplicationResponse' {Maybe ApiGatewayProxyConfig
apiGatewayProxy :: Maybe ApiGatewayProxyConfig
$sel:apiGatewayProxy:GetApplicationResponse' :: GetApplicationResponse -> Maybe ApiGatewayProxyConfig
apiGatewayProxy} -> Maybe ApiGatewayProxyConfig
apiGatewayProxy) (\s :: GetApplicationResponse
s@GetApplicationResponse' {} Maybe ApiGatewayProxyConfig
a -> GetApplicationResponse
s {$sel:apiGatewayProxy:GetApplicationResponse' :: Maybe ApiGatewayProxyConfig
apiGatewayProxy = Maybe ApiGatewayProxyConfig
a} :: GetApplicationResponse)

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

-- | The Amazon Resource Name (ARN) of the application.
getApplicationResponse_arn :: Lens.Lens' GetApplicationResponse (Prelude.Maybe Prelude.Text)
getApplicationResponse_arn :: Lens' GetApplicationResponse (Maybe Text)
getApplicationResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetApplicationResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:GetApplicationResponse' :: GetApplicationResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: GetApplicationResponse
s@GetApplicationResponse' {} Maybe Text
a -> GetApplicationResponse
s {$sel:arn:GetApplicationResponse' :: Maybe Text
arn = Maybe Text
a} :: GetApplicationResponse)

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

-- | A timestamp that indicates when the application is created.
getApplicationResponse_createdTime :: Lens.Lens' GetApplicationResponse (Prelude.Maybe Prelude.UTCTime)
getApplicationResponse_createdTime :: Lens' GetApplicationResponse (Maybe UTCTime)
getApplicationResponse_createdTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetApplicationResponse' {Maybe POSIX
createdTime :: Maybe POSIX
$sel:createdTime:GetApplicationResponse' :: GetApplicationResponse -> Maybe POSIX
createdTime} -> Maybe POSIX
createdTime) (\s :: GetApplicationResponse
s@GetApplicationResponse' {} Maybe POSIX
a -> GetApplicationResponse
s {$sel:createdTime:GetApplicationResponse' :: Maybe POSIX
createdTime = Maybe POSIX
a} :: GetApplicationResponse) 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 unique identifier of the environment.
getApplicationResponse_environmentId :: Lens.Lens' GetApplicationResponse (Prelude.Maybe Prelude.Text)
getApplicationResponse_environmentId :: Lens' GetApplicationResponse (Maybe Text)
getApplicationResponse_environmentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetApplicationResponse' {Maybe Text
environmentId :: Maybe Text
$sel:environmentId:GetApplicationResponse' :: GetApplicationResponse -> Maybe Text
environmentId} -> Maybe Text
environmentId) (\s :: GetApplicationResponse
s@GetApplicationResponse' {} Maybe Text
a -> GetApplicationResponse
s {$sel:environmentId:GetApplicationResponse' :: Maybe Text
environmentId = Maybe Text
a} :: GetApplicationResponse)

-- | Any error associated with the application resource.
getApplicationResponse_error :: Lens.Lens' GetApplicationResponse (Prelude.Maybe ErrorResponse)
getApplicationResponse_error :: Lens' GetApplicationResponse (Maybe ErrorResponse)
getApplicationResponse_error = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetApplicationResponse' {Maybe ErrorResponse
error :: Maybe ErrorResponse
$sel:error:GetApplicationResponse' :: GetApplicationResponse -> Maybe ErrorResponse
error} -> Maybe ErrorResponse
error) (\s :: GetApplicationResponse
s@GetApplicationResponse' {} Maybe ErrorResponse
a -> GetApplicationResponse
s {$sel:error:GetApplicationResponse' :: Maybe ErrorResponse
error = Maybe ErrorResponse
a} :: GetApplicationResponse)

-- | A timestamp that indicates when the application was last updated.
getApplicationResponse_lastUpdatedTime :: Lens.Lens' GetApplicationResponse (Prelude.Maybe Prelude.UTCTime)
getApplicationResponse_lastUpdatedTime :: Lens' GetApplicationResponse (Maybe UTCTime)
getApplicationResponse_lastUpdatedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetApplicationResponse' {Maybe POSIX
lastUpdatedTime :: Maybe POSIX
$sel:lastUpdatedTime:GetApplicationResponse' :: GetApplicationResponse -> Maybe POSIX
lastUpdatedTime} -> Maybe POSIX
lastUpdatedTime) (\s :: GetApplicationResponse
s@GetApplicationResponse' {} Maybe POSIX
a -> GetApplicationResponse
s {$sel:lastUpdatedTime:GetApplicationResponse' :: Maybe POSIX
lastUpdatedTime = Maybe POSIX
a} :: GetApplicationResponse) 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.
getApplicationResponse_name :: Lens.Lens' GetApplicationResponse (Prelude.Maybe Prelude.Text)
getApplicationResponse_name :: Lens' GetApplicationResponse (Maybe Text)
getApplicationResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetApplicationResponse' {Maybe Text
name :: Maybe Text
$sel:name:GetApplicationResponse' :: GetApplicationResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: GetApplicationResponse
s@GetApplicationResponse' {} Maybe Text
a -> GetApplicationResponse
s {$sel:name:GetApplicationResponse' :: Maybe Text
name = Maybe Text
a} :: GetApplicationResponse)

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

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

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

-- | 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.
getApplicationResponse_tags :: Lens.Lens' GetApplicationResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
getApplicationResponse_tags :: Lens' GetApplicationResponse (Maybe (HashMap Text Text))
getApplicationResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetApplicationResponse' {Maybe (Sensitive (HashMap Text Text))
tags :: Maybe (Sensitive (HashMap Text Text))
$sel:tags:GetApplicationResponse' :: GetApplicationResponse -> Maybe (Sensitive (HashMap Text Text))
tags} -> Maybe (Sensitive (HashMap Text Text))
tags) (\s :: GetApplicationResponse
s@GetApplicationResponse' {} Maybe (Sensitive (HashMap Text Text))
a -> GetApplicationResponse
s {$sel:tags:GetApplicationResponse' :: Maybe (Sensitive (HashMap Text Text))
tags = Maybe (Sensitive (HashMap Text Text))
a} :: GetApplicationResponse) 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 virtual private cloud (VPC).
getApplicationResponse_vpcId :: Lens.Lens' GetApplicationResponse (Prelude.Maybe Prelude.Text)
getApplicationResponse_vpcId :: Lens' GetApplicationResponse (Maybe Text)
getApplicationResponse_vpcId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetApplicationResponse' {Maybe Text
vpcId :: Maybe Text
$sel:vpcId:GetApplicationResponse' :: GetApplicationResponse -> Maybe Text
vpcId} -> Maybe Text
vpcId) (\s :: GetApplicationResponse
s@GetApplicationResponse' {} Maybe Text
a -> GetApplicationResponse
s {$sel:vpcId:GetApplicationResponse' :: Maybe Text
vpcId = Maybe Text
a} :: GetApplicationResponse)

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

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