{-# 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.KinesisAnalytics.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)
--
-- This documentation is for version 1 of the Amazon Kinesis Data Analytics
-- API, which only supports SQL applications. Version 2 of the API supports
-- SQL and Java applications. For more information about version 2, see
-- </kinesisanalytics/latest/apiv2/Welcome.html Amazon Kinesis Data Analytics API V2 Documentation>.
--
-- Stops the application from processing input data. You can stop an
-- application only if it is in the running state. You can use the
-- <https://docs.aws.amazon.com/kinesisanalytics/latest/dev/API_DescribeApplication.html DescribeApplication>
-- operation to find the application state. After the application is
-- stopped, Amazon Kinesis Analytics stops reading data from the input, the
-- application stops processing data, and there is no output written to the
-- destination.
--
-- This operation requires permissions to perform the
-- @kinesisanalytics:StopApplication@ action.
module Amazonka.KinesisAnalytics.StopApplication
  ( -- * Creating a Request
    StopApplication (..),
    newStopApplication,

    -- * Request Lenses
    stopApplication_applicationName,

    -- * 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.KinesisAnalytics.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'
  { -- | Name of the running application to stop.
    StopApplication -> Text
applicationName :: 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:
--
-- 'applicationName', 'stopApplication_applicationName' - Name of the running application to stop.
newStopApplication ::
  -- | 'applicationName'
  Prelude.Text ->
  StopApplication
newStopApplication :: Text -> StopApplication
newStopApplication Text
pApplicationName_ =
  StopApplication'
    { $sel:applicationName:StopApplication' :: Text
applicationName =
        Text
pApplicationName_
    }

-- | Name of the running application to stop.
stopApplication_applicationName :: Lens.Lens' StopApplication Prelude.Text
stopApplication_applicationName :: Lens' StopApplication Text
stopApplication_applicationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopApplication' {Text
applicationName :: Text
$sel:applicationName:StopApplication' :: StopApplication -> Text
applicationName} -> Text
applicationName) (\s :: StopApplication
s@StopApplication' {} Text
a -> StopApplication
s {$sel:applicationName:StopApplication' :: Text
applicationName = 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
applicationName :: Text
$sel:applicationName:StopApplication' :: StopApplication -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationName

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

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
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"KinesisAnalytics_20150814.StopApplication" ::
                          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 StopApplication where
  toJSON :: StopApplication -> Value
toJSON StopApplication' {Text
applicationName :: Text
$sel:applicationName:StopApplication' :: StopApplication -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"ApplicationName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
applicationName)
          ]
      )

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

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