{-# 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.ApplicationInsights.DescribeApplication
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describes the application.
module Amazonka.ApplicationInsights.DescribeApplication
  ( -- * Creating a Request
    DescribeApplication (..),
    newDescribeApplication,

    -- * Request Lenses
    describeApplication_resourceGroupName,

    -- * Destructuring the Response
    DescribeApplicationResponse (..),
    newDescribeApplicationResponse,

    -- * Response Lenses
    describeApplicationResponse_applicationInfo,
    describeApplicationResponse_httpStatus,
  )
where

import Amazonka.ApplicationInsights.Types
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

-- | /See:/ 'newDescribeApplication' smart constructor.
data DescribeApplication = DescribeApplication'
  { -- | The name of the resource group.
    DescribeApplication -> Text
resourceGroupName :: Prelude.Text
  }
  deriving (DescribeApplication -> DescribeApplication -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeApplication -> DescribeApplication -> Bool
$c/= :: DescribeApplication -> DescribeApplication -> Bool
== :: DescribeApplication -> DescribeApplication -> Bool
$c== :: DescribeApplication -> DescribeApplication -> Bool
Prelude.Eq, ReadPrec [DescribeApplication]
ReadPrec DescribeApplication
Int -> ReadS DescribeApplication
ReadS [DescribeApplication]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeApplication]
$creadListPrec :: ReadPrec [DescribeApplication]
readPrec :: ReadPrec DescribeApplication
$creadPrec :: ReadPrec DescribeApplication
readList :: ReadS [DescribeApplication]
$creadList :: ReadS [DescribeApplication]
readsPrec :: Int -> ReadS DescribeApplication
$creadsPrec :: Int -> ReadS DescribeApplication
Prelude.Read, Int -> DescribeApplication -> ShowS
[DescribeApplication] -> ShowS
DescribeApplication -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeApplication] -> ShowS
$cshowList :: [DescribeApplication] -> ShowS
show :: DescribeApplication -> String
$cshow :: DescribeApplication -> String
showsPrec :: Int -> DescribeApplication -> ShowS
$cshowsPrec :: Int -> DescribeApplication -> ShowS
Prelude.Show, forall x. Rep DescribeApplication x -> DescribeApplication
forall x. DescribeApplication -> Rep DescribeApplication x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeApplication x -> DescribeApplication
$cfrom :: forall x. DescribeApplication -> Rep DescribeApplication x
Prelude.Generic)

-- |
-- Create a value of 'DescribeApplication' 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:
--
-- 'resourceGroupName', 'describeApplication_resourceGroupName' - The name of the resource group.
newDescribeApplication ::
  -- | 'resourceGroupName'
  Prelude.Text ->
  DescribeApplication
newDescribeApplication :: Text -> DescribeApplication
newDescribeApplication Text
pResourceGroupName_ =
  DescribeApplication'
    { $sel:resourceGroupName:DescribeApplication' :: Text
resourceGroupName =
        Text
pResourceGroupName_
    }

-- | The name of the resource group.
describeApplication_resourceGroupName :: Lens.Lens' DescribeApplication Prelude.Text
describeApplication_resourceGroupName :: Lens' DescribeApplication Text
describeApplication_resourceGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeApplication' {Text
resourceGroupName :: Text
$sel:resourceGroupName:DescribeApplication' :: DescribeApplication -> Text
resourceGroupName} -> Text
resourceGroupName) (\s :: DescribeApplication
s@DescribeApplication' {} Text
a -> DescribeApplication
s {$sel:resourceGroupName:DescribeApplication' :: Text
resourceGroupName = Text
a} :: DescribeApplication)

instance Core.AWSRequest DescribeApplication where
  type
    AWSResponse DescribeApplication =
      DescribeApplicationResponse
  request :: (Service -> Service)
-> DescribeApplication -> Request DescribeApplication
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 DescribeApplication
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeApplication)))
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 ApplicationInfo -> Int -> DescribeApplicationResponse
DescribeApplicationResponse'
            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
"ApplicationInfo")
            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 DescribeApplication where
  hashWithSalt :: Int -> DescribeApplication -> Int
hashWithSalt Int
_salt DescribeApplication' {Text
resourceGroupName :: Text
$sel:resourceGroupName:DescribeApplication' :: DescribeApplication -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceGroupName

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

instance Data.ToHeaders DescribeApplication where
  toHeaders :: DescribeApplication -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"EC2WindowsBarleyService.DescribeApplication" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DescribeApplication where
  toJSON :: DescribeApplication -> Value
toJSON DescribeApplication' {Text
resourceGroupName :: Text
$sel:resourceGroupName:DescribeApplication' :: DescribeApplication -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"ResourceGroupName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
resourceGroupName)
          ]
      )

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

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

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

-- |
-- Create a value of 'DescribeApplicationResponse' 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:
--
-- 'applicationInfo', 'describeApplicationResponse_applicationInfo' - Information about the application.
--
-- 'httpStatus', 'describeApplicationResponse_httpStatus' - The response's http status code.
newDescribeApplicationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeApplicationResponse
newDescribeApplicationResponse :: Int -> DescribeApplicationResponse
newDescribeApplicationResponse Int
pHttpStatus_ =
  DescribeApplicationResponse'
    { $sel:applicationInfo:DescribeApplicationResponse' :: Maybe ApplicationInfo
applicationInfo =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeApplicationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the application.
describeApplicationResponse_applicationInfo :: Lens.Lens' DescribeApplicationResponse (Prelude.Maybe ApplicationInfo)
describeApplicationResponse_applicationInfo :: Lens' DescribeApplicationResponse (Maybe ApplicationInfo)
describeApplicationResponse_applicationInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeApplicationResponse' {Maybe ApplicationInfo
applicationInfo :: Maybe ApplicationInfo
$sel:applicationInfo:DescribeApplicationResponse' :: DescribeApplicationResponse -> Maybe ApplicationInfo
applicationInfo} -> Maybe ApplicationInfo
applicationInfo) (\s :: DescribeApplicationResponse
s@DescribeApplicationResponse' {} Maybe ApplicationInfo
a -> DescribeApplicationResponse
s {$sel:applicationInfo:DescribeApplicationResponse' :: Maybe ApplicationInfo
applicationInfo = Maybe ApplicationInfo
a} :: DescribeApplicationResponse)

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

instance Prelude.NFData DescribeApplicationResponse where
  rnf :: DescribeApplicationResponse -> ()
rnf DescribeApplicationResponse' {Int
Maybe ApplicationInfo
httpStatus :: Int
applicationInfo :: Maybe ApplicationInfo
$sel:httpStatus:DescribeApplicationResponse' :: DescribeApplicationResponse -> Int
$sel:applicationInfo:DescribeApplicationResponse' :: DescribeApplicationResponse -> Maybe ApplicationInfo
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ApplicationInfo
applicationInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus