{-# 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.CloudWatchLogs.StopQuery
-- 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 CloudWatch Logs Insights query that is in progress. If the query
-- has already ended, the operation returns an error indicating that the
-- specified query is not running.
module Amazonka.CloudWatchLogs.StopQuery
  ( -- * Creating a Request
    StopQuery (..),
    newStopQuery,

    -- * Request Lenses
    stopQuery_queryId,

    -- * Destructuring the Response
    StopQueryResponse (..),
    newStopQueryResponse,

    -- * Response Lenses
    stopQueryResponse_success,
    stopQueryResponse_httpStatus,
  )
where

import Amazonka.CloudWatchLogs.Types
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

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

-- |
-- Create a value of 'StopQuery' 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:
--
-- 'queryId', 'stopQuery_queryId' - The ID number of the query to stop. To find this ID number, use
-- @DescribeQueries@.
newStopQuery ::
  -- | 'queryId'
  Prelude.Text ->
  StopQuery
newStopQuery :: Text -> StopQuery
newStopQuery Text
pQueryId_ =
  StopQuery' {$sel:queryId:StopQuery' :: Text
queryId = Text
pQueryId_}

-- | The ID number of the query to stop. To find this ID number, use
-- @DescribeQueries@.
stopQuery_queryId :: Lens.Lens' StopQuery Prelude.Text
stopQuery_queryId :: Lens' StopQuery Text
stopQuery_queryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopQuery' {Text
queryId :: Text
$sel:queryId:StopQuery' :: StopQuery -> Text
queryId} -> Text
queryId) (\s :: StopQuery
s@StopQuery' {} Text
a -> StopQuery
s {$sel:queryId:StopQuery' :: Text
queryId = Text
a} :: StopQuery)

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

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

instance Data.ToHeaders StopQuery where
  toHeaders :: StopQuery -> 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
"Logs_20140328.StopQuery" :: 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 StopQuery where
  toJSON :: StopQuery -> Value
toJSON StopQuery' {Text
queryId :: Text
$sel:queryId:StopQuery' :: StopQuery -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"queryId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
queryId)]
      )

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

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

-- | /See:/ 'newStopQueryResponse' smart constructor.
data StopQueryResponse = StopQueryResponse'
  { -- | This is true if the query was stopped by the @StopQuery@ operation.
    StopQueryResponse -> Maybe Bool
success :: Prelude.Maybe Prelude.Bool,
    -- | The response's http status code.
    StopQueryResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StopQueryResponse -> StopQueryResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopQueryResponse -> StopQueryResponse -> Bool
$c/= :: StopQueryResponse -> StopQueryResponse -> Bool
== :: StopQueryResponse -> StopQueryResponse -> Bool
$c== :: StopQueryResponse -> StopQueryResponse -> Bool
Prelude.Eq, ReadPrec [StopQueryResponse]
ReadPrec StopQueryResponse
Int -> ReadS StopQueryResponse
ReadS [StopQueryResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopQueryResponse]
$creadListPrec :: ReadPrec [StopQueryResponse]
readPrec :: ReadPrec StopQueryResponse
$creadPrec :: ReadPrec StopQueryResponse
readList :: ReadS [StopQueryResponse]
$creadList :: ReadS [StopQueryResponse]
readsPrec :: Int -> ReadS StopQueryResponse
$creadsPrec :: Int -> ReadS StopQueryResponse
Prelude.Read, Int -> StopQueryResponse -> ShowS
[StopQueryResponse] -> ShowS
StopQueryResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopQueryResponse] -> ShowS
$cshowList :: [StopQueryResponse] -> ShowS
show :: StopQueryResponse -> String
$cshow :: StopQueryResponse -> String
showsPrec :: Int -> StopQueryResponse -> ShowS
$cshowsPrec :: Int -> StopQueryResponse -> ShowS
Prelude.Show, forall x. Rep StopQueryResponse x -> StopQueryResponse
forall x. StopQueryResponse -> Rep StopQueryResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StopQueryResponse x -> StopQueryResponse
$cfrom :: forall x. StopQueryResponse -> Rep StopQueryResponse x
Prelude.Generic)

-- |
-- Create a value of 'StopQueryResponse' 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:
--
-- 'success', 'stopQueryResponse_success' - This is true if the query was stopped by the @StopQuery@ operation.
--
-- 'httpStatus', 'stopQueryResponse_httpStatus' - The response's http status code.
newStopQueryResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StopQueryResponse
newStopQueryResponse :: Int -> StopQueryResponse
newStopQueryResponse Int
pHttpStatus_ =
  StopQueryResponse'
    { $sel:success:StopQueryResponse' :: Maybe Bool
success = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StopQueryResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | This is true if the query was stopped by the @StopQuery@ operation.
stopQueryResponse_success :: Lens.Lens' StopQueryResponse (Prelude.Maybe Prelude.Bool)
stopQueryResponse_success :: Lens' StopQueryResponse (Maybe Bool)
stopQueryResponse_success = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopQueryResponse' {Maybe Bool
success :: Maybe Bool
$sel:success:StopQueryResponse' :: StopQueryResponse -> Maybe Bool
success} -> Maybe Bool
success) (\s :: StopQueryResponse
s@StopQueryResponse' {} Maybe Bool
a -> StopQueryResponse
s {$sel:success:StopQueryResponse' :: Maybe Bool
success = Maybe Bool
a} :: StopQueryResponse)

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

instance Prelude.NFData StopQueryResponse where
  rnf :: StopQueryResponse -> ()
rnf StopQueryResponse' {Int
Maybe Bool
httpStatus :: Int
success :: Maybe Bool
$sel:httpStatus:StopQueryResponse' :: StopQueryResponse -> Int
$sel:success:StopQueryResponse' :: StopQueryResponse -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
success
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus