{-# 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.LaunchApp
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Launches the specified application as a stack in CloudFormation.
module Amazonka.SMS.LaunchApp
  ( -- * Creating a Request
    LaunchApp (..),
    newLaunchApp,

    -- * Request Lenses
    launchApp_appId,

    -- * Destructuring the Response
    LaunchAppResponse (..),
    newLaunchAppResponse,

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

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

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

instance Core.AWSRequest LaunchApp where
  type AWSResponse LaunchApp = LaunchAppResponse
  request :: (Service -> Service) -> LaunchApp -> Request LaunchApp
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 LaunchApp
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse LaunchApp)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> LaunchAppResponse
LaunchAppResponse'
            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))
      )

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

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

instance Data.ToHeaders LaunchApp where
  toHeaders :: LaunchApp -> 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.LaunchApp" ::
                          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 LaunchApp where
  toJSON :: LaunchApp -> Value
toJSON LaunchApp' {Maybe Text
appId :: Maybe Text
$sel:appId:LaunchApp' :: LaunchApp -> 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 LaunchApp where
  toPath :: LaunchApp -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

-- |
-- Create a value of 'LaunchAppResponse' 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', 'launchAppResponse_httpStatus' - The response's http status code.
newLaunchAppResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  LaunchAppResponse
newLaunchAppResponse :: Int -> LaunchAppResponse
newLaunchAppResponse Int
pHttpStatus_ =
  LaunchAppResponse' {$sel:httpStatus:LaunchAppResponse' :: Int
httpStatus = Int
pHttpStatus_}

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

instance Prelude.NFData LaunchAppResponse where
  rnf :: LaunchAppResponse -> ()
rnf LaunchAppResponse' {Int
httpStatus :: Int
$sel:httpStatus:LaunchAppResponse' :: LaunchAppResponse -> Int
..} = forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus