{-# 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.SMS.GetApp
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieve information about the specified application.
module Amazonka.SMS.GetApp
  ( -- * Creating a Request
    GetApp (..),
    newGetApp,

    -- * Request Lenses
    getApp_appId,

    -- * Destructuring the Response
    GetAppResponse (..),
    newGetAppResponse,

    -- * Response Lenses
    getAppResponse_appSummary,
    getAppResponse_serverGroups,
    getAppResponse_tags,
    getAppResponse_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.SMS.Types

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

-- |
-- Create a value of 'GetApp' 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:
--
-- 'appId', 'getApp_appId' - The ID of the application.
newGetApp ::
  GetApp
newGetApp :: GetApp
newGetApp = GetApp' {$sel:appId:GetApp' :: Maybe Text
appId = forall a. Maybe a
Prelude.Nothing}

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

instance Core.AWSRequest GetApp where
  type AWSResponse GetApp = GetAppResponse
  request :: (Service -> Service) -> GetApp -> Request GetApp
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 GetApp
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetApp)))
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 AppSummary
-> Maybe [ServerGroup] -> Maybe [Tag] -> Int -> GetAppResponse
GetAppResponse'
            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
"appSummary")
            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
"serverGroups" 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
"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 GetApp where
  hashWithSalt :: Int -> GetApp -> Int
hashWithSalt Int
_salt GetApp' {Maybe Text
appId :: Maybe Text
$sel:appId:GetApp' :: GetApp -> Maybe Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
appId

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

instance Data.ToHeaders GetApp where
  toHeaders :: GetApp -> 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
"AWSServerMigrationService_V2016_10_24.GetApp" ::
                          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 GetApp where
  toJSON :: GetApp -> Value
toJSON GetApp' {Maybe Text
appId :: Maybe Text
$sel:appId:GetApp' :: GetApp -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [(Key
"appId" 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
appId]
      )

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

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

-- | /See:/ 'newGetAppResponse' smart constructor.
data GetAppResponse = GetAppResponse'
  { -- | Information about the application.
    GetAppResponse -> Maybe AppSummary
appSummary :: Prelude.Maybe AppSummary,
    -- | The server groups that belong to the application.
    GetAppResponse -> Maybe [ServerGroup]
serverGroups :: Prelude.Maybe [ServerGroup],
    -- | The tags associated with the application.
    GetAppResponse -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The response's http status code.
    GetAppResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetAppResponse -> GetAppResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAppResponse -> GetAppResponse -> Bool
$c/= :: GetAppResponse -> GetAppResponse -> Bool
== :: GetAppResponse -> GetAppResponse -> Bool
$c== :: GetAppResponse -> GetAppResponse -> Bool
Prelude.Eq, ReadPrec [GetAppResponse]
ReadPrec GetAppResponse
Int -> ReadS GetAppResponse
ReadS [GetAppResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetAppResponse]
$creadListPrec :: ReadPrec [GetAppResponse]
readPrec :: ReadPrec GetAppResponse
$creadPrec :: ReadPrec GetAppResponse
readList :: ReadS [GetAppResponse]
$creadList :: ReadS [GetAppResponse]
readsPrec :: Int -> ReadS GetAppResponse
$creadsPrec :: Int -> ReadS GetAppResponse
Prelude.Read, Int -> GetAppResponse -> ShowS
[GetAppResponse] -> ShowS
GetAppResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAppResponse] -> ShowS
$cshowList :: [GetAppResponse] -> ShowS
show :: GetAppResponse -> String
$cshow :: GetAppResponse -> String
showsPrec :: Int -> GetAppResponse -> ShowS
$cshowsPrec :: Int -> GetAppResponse -> ShowS
Prelude.Show, forall x. Rep GetAppResponse x -> GetAppResponse
forall x. GetAppResponse -> Rep GetAppResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetAppResponse x -> GetAppResponse
$cfrom :: forall x. GetAppResponse -> Rep GetAppResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetAppResponse' 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:
--
-- 'appSummary', 'getAppResponse_appSummary' - Information about the application.
--
-- 'serverGroups', 'getAppResponse_serverGroups' - The server groups that belong to the application.
--
-- 'tags', 'getAppResponse_tags' - The tags associated with the application.
--
-- 'httpStatus', 'getAppResponse_httpStatus' - The response's http status code.
newGetAppResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetAppResponse
newGetAppResponse :: Int -> GetAppResponse
newGetAppResponse Int
pHttpStatus_ =
  GetAppResponse'
    { $sel:appSummary:GetAppResponse' :: Maybe AppSummary
appSummary = forall a. Maybe a
Prelude.Nothing,
      $sel:serverGroups:GetAppResponse' :: Maybe [ServerGroup]
serverGroups = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:GetAppResponse' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetAppResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the application.
getAppResponse_appSummary :: Lens.Lens' GetAppResponse (Prelude.Maybe AppSummary)
getAppResponse_appSummary :: Lens' GetAppResponse (Maybe AppSummary)
getAppResponse_appSummary = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAppResponse' {Maybe AppSummary
appSummary :: Maybe AppSummary
$sel:appSummary:GetAppResponse' :: GetAppResponse -> Maybe AppSummary
appSummary} -> Maybe AppSummary
appSummary) (\s :: GetAppResponse
s@GetAppResponse' {} Maybe AppSummary
a -> GetAppResponse
s {$sel:appSummary:GetAppResponse' :: Maybe AppSummary
appSummary = Maybe AppSummary
a} :: GetAppResponse)

-- | The server groups that belong to the application.
getAppResponse_serverGroups :: Lens.Lens' GetAppResponse (Prelude.Maybe [ServerGroup])
getAppResponse_serverGroups :: Lens' GetAppResponse (Maybe [ServerGroup])
getAppResponse_serverGroups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAppResponse' {Maybe [ServerGroup]
serverGroups :: Maybe [ServerGroup]
$sel:serverGroups:GetAppResponse' :: GetAppResponse -> Maybe [ServerGroup]
serverGroups} -> Maybe [ServerGroup]
serverGroups) (\s :: GetAppResponse
s@GetAppResponse' {} Maybe [ServerGroup]
a -> GetAppResponse
s {$sel:serverGroups:GetAppResponse' :: Maybe [ServerGroup]
serverGroups = Maybe [ServerGroup]
a} :: GetAppResponse) 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 tags associated with the application.
getAppResponse_tags :: Lens.Lens' GetAppResponse (Prelude.Maybe [Tag])
getAppResponse_tags :: Lens' GetAppResponse (Maybe [Tag])
getAppResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAppResponse' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:GetAppResponse' :: GetAppResponse -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: GetAppResponse
s@GetAppResponse' {} Maybe [Tag]
a -> GetAppResponse
s {$sel:tags:GetAppResponse' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: GetAppResponse) 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.
getAppResponse_httpStatus :: Lens.Lens' GetAppResponse Prelude.Int
getAppResponse_httpStatus :: Lens' GetAppResponse Int
getAppResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAppResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetAppResponse' :: GetAppResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetAppResponse
s@GetAppResponse' {} Int
a -> GetAppResponse
s {$sel:httpStatus:GetAppResponse' :: Int
httpStatus = Int
a} :: GetAppResponse)

instance Prelude.NFData GetAppResponse where
  rnf :: GetAppResponse -> ()
rnf GetAppResponse' {Int
Maybe [Tag]
Maybe [ServerGroup]
Maybe AppSummary
httpStatus :: Int
tags :: Maybe [Tag]
serverGroups :: Maybe [ServerGroup]
appSummary :: Maybe AppSummary
$sel:httpStatus:GetAppResponse' :: GetAppResponse -> Int
$sel:tags:GetAppResponse' :: GetAppResponse -> Maybe [Tag]
$sel:serverGroups:GetAppResponse' :: GetAppResponse -> Maybe [ServerGroup]
$sel:appSummary:GetAppResponse' :: GetAppResponse -> Maybe AppSummary
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AppSummary
appSummary
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ServerGroup]
serverGroups
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus