{-# 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.KinesisAnalyticsV2.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 the application from processing data. You can stop an application
-- only if it is in the running status, unless you set the @Force@
-- parameter to @true@.
--
-- You can use the DescribeApplication operation to find the application
-- status.
--
-- Kinesis Data Analytics takes a snapshot when the application is stopped,
-- unless @Force@ is set to @true@.
module Amazonka.KinesisAnalyticsV2.StopApplication
  ( -- * Creating a Request
    StopApplication (..),
    newStopApplication,

    -- * Request Lenses
    stopApplication_force,
    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.KinesisAnalyticsV2.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'
  { -- | Set to @true@ to force the application to stop. If you set @Force@ to
    -- @true@, Kinesis Data Analytics stops the application without taking a
    -- snapshot.
    --
    -- Force-stopping your application may lead to data loss or duplication. To
    -- prevent data loss or duplicate processing of data during application
    -- restarts, we recommend you to take frequent snapshots of your
    -- application.
    --
    -- You can only force stop a Flink-based Kinesis Data Analytics
    -- application. You can\'t force stop a SQL-based Kinesis Data Analytics
    -- application.
    --
    -- The application must be in the @STARTING@, @UPDATING@, @STOPPING@,
    -- @AUTOSCALING@, or @RUNNING@ status.
    StopApplication -> Maybe Bool
force :: Prelude.Maybe Prelude.Bool,
    -- | The 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:
--
-- 'force', 'stopApplication_force' - Set to @true@ to force the application to stop. If you set @Force@ to
-- @true@, Kinesis Data Analytics stops the application without taking a
-- snapshot.
--
-- Force-stopping your application may lead to data loss or duplication. To
-- prevent data loss or duplicate processing of data during application
-- restarts, we recommend you to take frequent snapshots of your
-- application.
--
-- You can only force stop a Flink-based Kinesis Data Analytics
-- application. You can\'t force stop a SQL-based Kinesis Data Analytics
-- application.
--
-- The application must be in the @STARTING@, @UPDATING@, @STOPPING@,
-- @AUTOSCALING@, or @RUNNING@ status.
--
-- 'applicationName', 'stopApplication_applicationName' - The name of the running application to stop.
newStopApplication ::
  -- | 'applicationName'
  Prelude.Text ->
  StopApplication
newStopApplication :: Text -> StopApplication
newStopApplication Text
pApplicationName_ =
  StopApplication'
    { $sel:force:StopApplication' :: Maybe Bool
force = forall a. Maybe a
Prelude.Nothing,
      $sel:applicationName:StopApplication' :: Text
applicationName = Text
pApplicationName_
    }

-- | Set to @true@ to force the application to stop. If you set @Force@ to
-- @true@, Kinesis Data Analytics stops the application without taking a
-- snapshot.
--
-- Force-stopping your application may lead to data loss or duplication. To
-- prevent data loss or duplicate processing of data during application
-- restarts, we recommend you to take frequent snapshots of your
-- application.
--
-- You can only force stop a Flink-based Kinesis Data Analytics
-- application. You can\'t force stop a SQL-based Kinesis Data Analytics
-- application.
--
-- The application must be in the @STARTING@, @UPDATING@, @STOPPING@,
-- @AUTOSCALING@, or @RUNNING@ status.
stopApplication_force :: Lens.Lens' StopApplication (Prelude.Maybe Prelude.Bool)
stopApplication_force :: Lens' StopApplication (Maybe Bool)
stopApplication_force = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopApplication' {Maybe Bool
force :: Maybe Bool
$sel:force:StopApplication' :: StopApplication -> Maybe Bool
force} -> Maybe Bool
force) (\s :: StopApplication
s@StopApplication' {} Maybe Bool
a -> StopApplication
s {$sel:force:StopApplication' :: Maybe Bool
force = Maybe Bool
a} :: StopApplication)

-- | The 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' {Maybe Bool
Text
applicationName :: Text
force :: Maybe Bool
$sel:applicationName:StopApplication' :: StopApplication -> Text
$sel:force:StopApplication' :: StopApplication -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
force
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationName

instance Prelude.NFData StopApplication where
  rnf :: StopApplication -> ()
rnf StopApplication' {Maybe Bool
Text
applicationName :: Text
force :: Maybe Bool
$sel:applicationName:StopApplication' :: StopApplication -> Text
$sel:force:StopApplication' :: StopApplication -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
force
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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_20180523.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' {Maybe Bool
Text
applicationName :: Text
force :: Maybe Bool
$sel:applicationName:StopApplication' :: StopApplication -> Text
$sel:force:StopApplication' :: StopApplication -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Force" 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 Bool
force,
            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