{-# 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.EMRServerless.StopApplication
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Stops a specified application and releases initial capacity if
-- configured. All scheduled and running jobs must be completed or
-- cancelled before stopping an application.
module Amazonka.EMRServerless.StopApplication
  ( -- * Creating a Request
    StopApplication (..),
    newStopApplication,

    -- * Request Lenses
    stopApplication_applicationId,

    -- * Destructuring the Response
    StopApplicationResponse (..),
    newStopApplicationResponse,

    -- * Response Lenses
    stopApplicationResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EMRServerless.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

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

-- |
-- Create a value of 'StopApplication' 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:
--
-- 'applicationId', 'stopApplication_applicationId' - The ID of the application to stop.
newStopApplication ::
  -- | 'applicationId'
  Prelude.Text ->
  StopApplication
newStopApplication :: Text -> StopApplication
newStopApplication Text
pApplicationId_ =
  StopApplication' {$sel:applicationId:StopApplication' :: Text
applicationId = Text
pApplicationId_}

-- | The ID of the application to stop.
stopApplication_applicationId :: Lens.Lens' StopApplication Prelude.Text
stopApplication_applicationId :: Lens' StopApplication Text
stopApplication_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopApplication' {Text
applicationId :: Text
$sel:applicationId:StopApplication' :: StopApplication -> Text
applicationId} -> Text
applicationId) (\s :: StopApplication
s@StopApplication' {} Text
a -> StopApplication
s {$sel:applicationId:StopApplication' :: Text
applicationId = Text
a} :: StopApplication)

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

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

instance Data.ToHeaders StopApplication where
  toHeaders :: StopApplication -> 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 StopApplication where
  toJSON :: StopApplication -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

instance Data.ToPath StopApplication where
  toPath :: StopApplication -> ByteString
toPath StopApplication' {Text
applicationId :: Text
$sel:applicationId:StopApplication' :: StopApplication -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/applications/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationId, ByteString
"/stop"]

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

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

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

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

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