{-# 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.ServiceCatalogAppRegistry.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)
--
-- Retrieves metadata information about one of your applications. The
-- application can be specified either by its unique ID or by its name
-- (which is unique within one account in one region at a given point in
-- time). Specify by ID in automated workflows if you want to make sure
-- that the exact same application is returned or a
-- @ResourceNotFoundException@ is thrown, avoiding the ABA addressing
-- problem.
module Amazonka.ServiceCatalogAppRegistry.GetApplication
  ( -- * Creating a Request
    GetApplication (..),
    newGetApplication,

    -- * Request Lenses
    getApplication_application,

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

    -- * Response Lenses
    getApplicationResponse_arn,
    getApplicationResponse_associatedResourceCount,
    getApplicationResponse_creationTime,
    getApplicationResponse_description,
    getApplicationResponse_id,
    getApplicationResponse_integrations,
    getApplicationResponse_lastUpdateTime,
    getApplicationResponse_name,
    getApplicationResponse_tags,
    getApplicationResponse_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.ServiceCatalogAppRegistry.Types

-- | /See:/ 'newGetApplication' smart constructor.
data GetApplication = GetApplication'
  { -- | The name or ID of the application.
    GetApplication -> Text
application :: 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:
--
-- 'application', 'getApplication_application' - The name or ID of the application.
newGetApplication ::
  -- | 'application'
  Prelude.Text ->
  GetApplication
newGetApplication :: Text -> GetApplication
newGetApplication Text
pApplication_ =
  GetApplication' {$sel:application:GetApplication' :: Text
application = Text
pApplication_}

-- | The name or ID of the application.
getApplication_application :: Lens.Lens' GetApplication Prelude.Text
getApplication_application :: Lens' GetApplication Text
getApplication_application = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetApplication' {Text
application :: Text
$sel:application:GetApplication' :: GetApplication -> Text
application} -> Text
application) (\s :: GetApplication
s@GetApplication' {} Text
a -> GetApplication
s {$sel:application:GetApplication' :: Text
application = 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 Text
-> Maybe Natural
-> Maybe ISO8601
-> Maybe Text
-> Maybe Text
-> Maybe Integrations
-> Maybe ISO8601
-> Maybe Text
-> Maybe (HashMap Text 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
"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
"associatedResourceCount")
            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
"creationTime")
            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
"description")
            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
"id")
            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
"integrations")
            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
"lastUpdateTime")
            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
"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 GetApplication where
  hashWithSalt :: Int -> GetApplication -> Int
hashWithSalt Int
_salt GetApplication' {Text
application :: Text
$sel:application:GetApplication' :: GetApplication -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
application

instance Prelude.NFData GetApplication where
  rnf :: GetApplication -> ()
rnf GetApplication' {Text
application :: Text
$sel:application:GetApplication' :: GetApplication -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
application

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
application :: Text
$sel:application:GetApplication' :: GetApplication -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/applications/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
application]

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 Amazon resource name (ARN) that specifies the application across
    -- services.
    GetApplicationResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The number of top-level resources that were registered as part of this
    -- application.
    GetApplicationResponse -> Maybe Natural
associatedResourceCount :: Prelude.Maybe Prelude.Natural,
    -- | The ISO-8601 formatted timestamp of the moment when the application was
    -- created.
    GetApplicationResponse -> Maybe ISO8601
creationTime :: Prelude.Maybe Data.ISO8601,
    -- | The description of the application.
    GetApplicationResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the application.
    GetApplicationResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The information about the integration of the application with other
    -- services, such as Resource Groups.
    GetApplicationResponse -> Maybe Integrations
integrations :: Prelude.Maybe Integrations,
    -- | The ISO-8601 formatted timestamp of the moment when the application was
    -- last updated.
    GetApplicationResponse -> Maybe ISO8601
lastUpdateTime :: Prelude.Maybe Data.ISO8601,
    -- | The name of the application. The name must be unique in the region in
    -- which you are creating the application.
    GetApplicationResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | Key-value pairs associated with the application.
    GetApplicationResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text 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, ReadPrec [GetApplicationResponse]
ReadPrec GetApplicationResponse
Int -> ReadS GetApplicationResponse
ReadS [GetApplicationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetApplicationResponse]
$creadListPrec :: ReadPrec [GetApplicationResponse]
readPrec :: ReadPrec GetApplicationResponse
$creadPrec :: ReadPrec GetApplicationResponse
readList :: ReadS [GetApplicationResponse]
$creadList :: ReadS [GetApplicationResponse]
readsPrec :: Int -> ReadS GetApplicationResponse
$creadsPrec :: Int -> ReadS GetApplicationResponse
Prelude.Read, 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:
--
-- 'arn', 'getApplicationResponse_arn' - The Amazon resource name (ARN) that specifies the application across
-- services.
--
-- 'associatedResourceCount', 'getApplicationResponse_associatedResourceCount' - The number of top-level resources that were registered as part of this
-- application.
--
-- 'creationTime', 'getApplicationResponse_creationTime' - The ISO-8601 formatted timestamp of the moment when the application was
-- created.
--
-- 'description', 'getApplicationResponse_description' - The description of the application.
--
-- 'id', 'getApplicationResponse_id' - The identifier of the application.
--
-- 'integrations', 'getApplicationResponse_integrations' - The information about the integration of the application with other
-- services, such as Resource Groups.
--
-- 'lastUpdateTime', 'getApplicationResponse_lastUpdateTime' - The ISO-8601 formatted timestamp of the moment when the application was
-- last updated.
--
-- 'name', 'getApplicationResponse_name' - The name of the application. The name must be unique in the region in
-- which you are creating the application.
--
-- 'tags', 'getApplicationResponse_tags' - Key-value pairs associated with the application.
--
-- 'httpStatus', 'getApplicationResponse_httpStatus' - The response's http status code.
newGetApplicationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetApplicationResponse
newGetApplicationResponse :: Int -> GetApplicationResponse
newGetApplicationResponse Int
pHttpStatus_ =
  GetApplicationResponse'
    { $sel:arn:GetApplicationResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:associatedResourceCount:GetApplicationResponse' :: Maybe Natural
associatedResourceCount = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:GetApplicationResponse' :: Maybe ISO8601
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:description:GetApplicationResponse' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:id:GetApplicationResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:integrations:GetApplicationResponse' :: Maybe Integrations
integrations = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdateTime:GetApplicationResponse' :: Maybe ISO8601
lastUpdateTime = forall a. Maybe a
Prelude.Nothing,
      $sel:name:GetApplicationResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:GetApplicationResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetApplicationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon resource name (ARN) that specifies the application across
-- services.
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 number of top-level resources that were registered as part of this
-- application.
getApplicationResponse_associatedResourceCount :: Lens.Lens' GetApplicationResponse (Prelude.Maybe Prelude.Natural)
getApplicationResponse_associatedResourceCount :: Lens' GetApplicationResponse (Maybe Natural)
getApplicationResponse_associatedResourceCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetApplicationResponse' {Maybe Natural
associatedResourceCount :: Maybe Natural
$sel:associatedResourceCount:GetApplicationResponse' :: GetApplicationResponse -> Maybe Natural
associatedResourceCount} -> Maybe Natural
associatedResourceCount) (\s :: GetApplicationResponse
s@GetApplicationResponse' {} Maybe Natural
a -> GetApplicationResponse
s {$sel:associatedResourceCount:GetApplicationResponse' :: Maybe Natural
associatedResourceCount = Maybe Natural
a} :: GetApplicationResponse)

-- | The ISO-8601 formatted timestamp of the moment when the application was
-- created.
getApplicationResponse_creationTime :: Lens.Lens' GetApplicationResponse (Prelude.Maybe Prelude.UTCTime)
getApplicationResponse_creationTime :: Lens' GetApplicationResponse (Maybe UTCTime)
getApplicationResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetApplicationResponse' {Maybe ISO8601
creationTime :: Maybe ISO8601
$sel:creationTime:GetApplicationResponse' :: GetApplicationResponse -> Maybe ISO8601
creationTime} -> Maybe ISO8601
creationTime) (\s :: GetApplicationResponse
s@GetApplicationResponse' {} Maybe ISO8601
a -> GetApplicationResponse
s {$sel:creationTime:GetApplicationResponse' :: Maybe ISO8601
creationTime = Maybe ISO8601
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 description of the application.
getApplicationResponse_description :: Lens.Lens' GetApplicationResponse (Prelude.Maybe Prelude.Text)
getApplicationResponse_description :: Lens' GetApplicationResponse (Maybe Text)
getApplicationResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetApplicationResponse' {Maybe Text
description :: Maybe Text
$sel:description:GetApplicationResponse' :: GetApplicationResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: GetApplicationResponse
s@GetApplicationResponse' {} Maybe Text
a -> GetApplicationResponse
s {$sel:description:GetApplicationResponse' :: Maybe Text
description = Maybe Text
a} :: GetApplicationResponse)

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

-- | The information about the integration of the application with other
-- services, such as Resource Groups.
getApplicationResponse_integrations :: Lens.Lens' GetApplicationResponse (Prelude.Maybe Integrations)
getApplicationResponse_integrations :: Lens' GetApplicationResponse (Maybe Integrations)
getApplicationResponse_integrations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetApplicationResponse' {Maybe Integrations
integrations :: Maybe Integrations
$sel:integrations:GetApplicationResponse' :: GetApplicationResponse -> Maybe Integrations
integrations} -> Maybe Integrations
integrations) (\s :: GetApplicationResponse
s@GetApplicationResponse' {} Maybe Integrations
a -> GetApplicationResponse
s {$sel:integrations:GetApplicationResponse' :: Maybe Integrations
integrations = Maybe Integrations
a} :: GetApplicationResponse)

-- | The ISO-8601 formatted timestamp of the moment when the application was
-- last updated.
getApplicationResponse_lastUpdateTime :: Lens.Lens' GetApplicationResponse (Prelude.Maybe Prelude.UTCTime)
getApplicationResponse_lastUpdateTime :: Lens' GetApplicationResponse (Maybe UTCTime)
getApplicationResponse_lastUpdateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetApplicationResponse' {Maybe ISO8601
lastUpdateTime :: Maybe ISO8601
$sel:lastUpdateTime:GetApplicationResponse' :: GetApplicationResponse -> Maybe ISO8601
lastUpdateTime} -> Maybe ISO8601
lastUpdateTime) (\s :: GetApplicationResponse
s@GetApplicationResponse' {} Maybe ISO8601
a -> GetApplicationResponse
s {$sel:lastUpdateTime:GetApplicationResponse' :: Maybe ISO8601
lastUpdateTime = Maybe ISO8601
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. The name must be unique in the region in
-- which you are creating 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)

-- | Key-value pairs associated with the application.
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 (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:GetApplicationResponse' :: GetApplicationResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: GetApplicationResponse
s@GetApplicationResponse' {} Maybe (HashMap Text Text)
a -> GetApplicationResponse
s {$sel:tags:GetApplicationResponse' :: Maybe (HashMap Text Text)
tags = Maybe (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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | 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 Natural
Maybe Text
Maybe (HashMap Text Text)
Maybe ISO8601
Maybe Integrations
httpStatus :: Int
tags :: Maybe (HashMap Text Text)
name :: Maybe Text
lastUpdateTime :: Maybe ISO8601
integrations :: Maybe Integrations
id :: Maybe Text
description :: Maybe Text
creationTime :: Maybe ISO8601
associatedResourceCount :: Maybe Natural
arn :: Maybe Text
$sel:httpStatus:GetApplicationResponse' :: GetApplicationResponse -> Int
$sel:tags:GetApplicationResponse' :: GetApplicationResponse -> Maybe (HashMap Text Text)
$sel:name:GetApplicationResponse' :: GetApplicationResponse -> Maybe Text
$sel:lastUpdateTime:GetApplicationResponse' :: GetApplicationResponse -> Maybe ISO8601
$sel:integrations:GetApplicationResponse' :: GetApplicationResponse -> Maybe Integrations
$sel:id:GetApplicationResponse' :: GetApplicationResponse -> Maybe Text
$sel:description:GetApplicationResponse' :: GetApplicationResponse -> Maybe Text
$sel:creationTime:GetApplicationResponse' :: GetApplicationResponse -> Maybe ISO8601
$sel:associatedResourceCount:GetApplicationResponse' :: GetApplicationResponse -> Maybe Natural
$sel:arn:GetApplicationResponse' :: GetApplicationResponse -> Maybe Text
..} =
    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 Natural
associatedResourceCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
creationTime
      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 Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integrations
integrations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
lastUpdateTime
      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 (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus