{-# 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.ResilienceHub.DescribeApp
-- 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 an AWS Resilience Hub application.
module Amazonka.ResilienceHub.DescribeApp
  ( -- * Creating a Request
    DescribeApp (..),
    newDescribeApp,

    -- * Request Lenses
    describeApp_appArn,

    -- * Destructuring the Response
    DescribeAppResponse (..),
    newDescribeAppResponse,

    -- * Response Lenses
    describeAppResponse_httpStatus,
    describeAppResponse_app,
  )
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 Amazonka.ResilienceHub.Types
import qualified Amazonka.Response as Response

-- | /See:/ 'newDescribeApp' smart constructor.
data DescribeApp = DescribeApp'
  { -- | The Amazon Resource Name (ARN) of the application. The format for this
    -- ARN is: arn:@partition@:resiliencehub:@region@:@account@:app\/@app-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 /AWS General Reference/.
    DescribeApp -> Text
appArn :: Prelude.Text
  }
  deriving (DescribeApp -> DescribeApp -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeApp -> DescribeApp -> Bool
$c/= :: DescribeApp -> DescribeApp -> Bool
== :: DescribeApp -> DescribeApp -> Bool
$c== :: DescribeApp -> DescribeApp -> Bool
Prelude.Eq, ReadPrec [DescribeApp]
ReadPrec DescribeApp
Int -> ReadS DescribeApp
ReadS [DescribeApp]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeApp]
$creadListPrec :: ReadPrec [DescribeApp]
readPrec :: ReadPrec DescribeApp
$creadPrec :: ReadPrec DescribeApp
readList :: ReadS [DescribeApp]
$creadList :: ReadS [DescribeApp]
readsPrec :: Int -> ReadS DescribeApp
$creadsPrec :: Int -> ReadS DescribeApp
Prelude.Read, Int -> DescribeApp -> ShowS
[DescribeApp] -> ShowS
DescribeApp -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeApp] -> ShowS
$cshowList :: [DescribeApp] -> ShowS
show :: DescribeApp -> String
$cshow :: DescribeApp -> String
showsPrec :: Int -> DescribeApp -> ShowS
$cshowsPrec :: Int -> DescribeApp -> ShowS
Prelude.Show, forall x. Rep DescribeApp x -> DescribeApp
forall x. DescribeApp -> Rep DescribeApp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeApp x -> DescribeApp
$cfrom :: forall x. DescribeApp -> Rep DescribeApp x
Prelude.Generic)

-- |
-- Create a value of 'DescribeApp' 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:
--
-- 'appArn', 'describeApp_appArn' - The Amazon Resource Name (ARN) of the application. The format for this
-- ARN is: arn:@partition@:resiliencehub:@region@:@account@:app\/@app-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 /AWS General Reference/.
newDescribeApp ::
  -- | 'appArn'
  Prelude.Text ->
  DescribeApp
newDescribeApp :: Text -> DescribeApp
newDescribeApp Text
pAppArn_ =
  DescribeApp' {$sel:appArn:DescribeApp' :: Text
appArn = Text
pAppArn_}

-- | The Amazon Resource Name (ARN) of the application. The format for this
-- ARN is: arn:@partition@:resiliencehub:@region@:@account@:app\/@app-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 /AWS General Reference/.
describeApp_appArn :: Lens.Lens' DescribeApp Prelude.Text
describeApp_appArn :: Lens' DescribeApp Text
describeApp_appArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeApp' {Text
appArn :: Text
$sel:appArn:DescribeApp' :: DescribeApp -> Text
appArn} -> Text
appArn) (\s :: DescribeApp
s@DescribeApp' {} Text
a -> DescribeApp
s {$sel:appArn:DescribeApp' :: Text
appArn = Text
a} :: DescribeApp)

instance Core.AWSRequest DescribeApp where
  type AWSResponse DescribeApp = DescribeAppResponse
  request :: (Service -> Service) -> DescribeApp -> Request DescribeApp
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 DescribeApp
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeApp)))
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 ->
          Int -> App -> DescribeAppResponse
DescribeAppResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"app")
      )

instance Prelude.Hashable DescribeApp where
  hashWithSalt :: Int -> DescribeApp -> Int
hashWithSalt Int
_salt DescribeApp' {Text
appArn :: Text
$sel:appArn:DescribeApp' :: DescribeApp -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
appArn

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

instance Data.ToHeaders DescribeApp where
  toHeaders :: DescribeApp -> 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 DescribeApp where
  toJSON :: DescribeApp -> Value
toJSON DescribeApp' {Text
appArn :: Text
$sel:appArn:DescribeApp' :: DescribeApp -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"appArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
appArn)]
      )

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

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

-- | /See:/ 'newDescribeAppResponse' smart constructor.
data DescribeAppResponse = DescribeAppResponse'
  { -- | The response's http status code.
    DescribeAppResponse -> Int
httpStatus :: Prelude.Int,
    -- | The specified application, returned as an object with details including
    -- compliance status, creation time, description, resiliency score, and
    -- more.
    DescribeAppResponse -> App
app :: App
  }
  deriving (DescribeAppResponse -> DescribeAppResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeAppResponse -> DescribeAppResponse -> Bool
$c/= :: DescribeAppResponse -> DescribeAppResponse -> Bool
== :: DescribeAppResponse -> DescribeAppResponse -> Bool
$c== :: DescribeAppResponse -> DescribeAppResponse -> Bool
Prelude.Eq, Int -> DescribeAppResponse -> ShowS
[DescribeAppResponse] -> ShowS
DescribeAppResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeAppResponse] -> ShowS
$cshowList :: [DescribeAppResponse] -> ShowS
show :: DescribeAppResponse -> String
$cshow :: DescribeAppResponse -> String
showsPrec :: Int -> DescribeAppResponse -> ShowS
$cshowsPrec :: Int -> DescribeAppResponse -> ShowS
Prelude.Show, forall x. Rep DescribeAppResponse x -> DescribeAppResponse
forall x. DescribeAppResponse -> Rep DescribeAppResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeAppResponse x -> DescribeAppResponse
$cfrom :: forall x. DescribeAppResponse -> Rep DescribeAppResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeAppResponse' 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:
--
-- 'httpStatus', 'describeAppResponse_httpStatus' - The response's http status code.
--
-- 'app', 'describeAppResponse_app' - The specified application, returned as an object with details including
-- compliance status, creation time, description, resiliency score, and
-- more.
newDescribeAppResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'app'
  App ->
  DescribeAppResponse
newDescribeAppResponse :: Int -> App -> DescribeAppResponse
newDescribeAppResponse Int
pHttpStatus_ App
pApp_ =
  DescribeAppResponse'
    { $sel:httpStatus:DescribeAppResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:app:DescribeAppResponse' :: App
app = App
pApp_
    }

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

-- | The specified application, returned as an object with details including
-- compliance status, creation time, description, resiliency score, and
-- more.
describeAppResponse_app :: Lens.Lens' DescribeAppResponse App
describeAppResponse_app :: Lens' DescribeAppResponse App
describeAppResponse_app = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAppResponse' {App
app :: App
$sel:app:DescribeAppResponse' :: DescribeAppResponse -> App
app} -> App
app) (\s :: DescribeAppResponse
s@DescribeAppResponse' {} App
a -> DescribeAppResponse
s {$sel:app:DescribeAppResponse' :: App
app = App
a} :: DescribeAppResponse)

instance Prelude.NFData DescribeAppResponse where
  rnf :: DescribeAppResponse -> ()
rnf DescribeAppResponse' {Int
App
app :: App
httpStatus :: Int
$sel:app:DescribeAppResponse' :: DescribeAppResponse -> App
$sel:httpStatus:DescribeAppResponse' :: DescribeAppResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf App
app