{-# 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.Athena.GetQueryRuntimeStatistics
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns query execution runtime statistics related to a single execution
-- of a query if you have access to the workgroup in which the query ran.
-- Query execution runtime statistics are returned only when
-- QueryExecutionStatus$State is in a SUCCEEDED or FAILED state.
-- Stage-level input and output row count and data size statistics are not
-- shown when a query has row-level filters defined in Lake Formation.
module Amazonka.Athena.GetQueryRuntimeStatistics
  ( -- * Creating a Request
    GetQueryRuntimeStatistics (..),
    newGetQueryRuntimeStatistics,

    -- * Request Lenses
    getQueryRuntimeStatistics_queryExecutionId,

    -- * Destructuring the Response
    GetQueryRuntimeStatisticsResponse (..),
    newGetQueryRuntimeStatisticsResponse,

    -- * Response Lenses
    getQueryRuntimeStatisticsResponse_queryRuntimeStatistics,
    getQueryRuntimeStatisticsResponse_httpStatus,
  )
where

import Amazonka.Athena.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:/ 'newGetQueryRuntimeStatistics' smart constructor.
data GetQueryRuntimeStatistics = GetQueryRuntimeStatistics'
  { -- | The unique ID of the query execution.
    GetQueryRuntimeStatistics -> Text
queryExecutionId :: Prelude.Text
  }
  deriving (GetQueryRuntimeStatistics -> GetQueryRuntimeStatistics -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetQueryRuntimeStatistics -> GetQueryRuntimeStatistics -> Bool
$c/= :: GetQueryRuntimeStatistics -> GetQueryRuntimeStatistics -> Bool
== :: GetQueryRuntimeStatistics -> GetQueryRuntimeStatistics -> Bool
$c== :: GetQueryRuntimeStatistics -> GetQueryRuntimeStatistics -> Bool
Prelude.Eq, ReadPrec [GetQueryRuntimeStatistics]
ReadPrec GetQueryRuntimeStatistics
Int -> ReadS GetQueryRuntimeStatistics
ReadS [GetQueryRuntimeStatistics]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetQueryRuntimeStatistics]
$creadListPrec :: ReadPrec [GetQueryRuntimeStatistics]
readPrec :: ReadPrec GetQueryRuntimeStatistics
$creadPrec :: ReadPrec GetQueryRuntimeStatistics
readList :: ReadS [GetQueryRuntimeStatistics]
$creadList :: ReadS [GetQueryRuntimeStatistics]
readsPrec :: Int -> ReadS GetQueryRuntimeStatistics
$creadsPrec :: Int -> ReadS GetQueryRuntimeStatistics
Prelude.Read, Int -> GetQueryRuntimeStatistics -> ShowS
[GetQueryRuntimeStatistics] -> ShowS
GetQueryRuntimeStatistics -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetQueryRuntimeStatistics] -> ShowS
$cshowList :: [GetQueryRuntimeStatistics] -> ShowS
show :: GetQueryRuntimeStatistics -> String
$cshow :: GetQueryRuntimeStatistics -> String
showsPrec :: Int -> GetQueryRuntimeStatistics -> ShowS
$cshowsPrec :: Int -> GetQueryRuntimeStatistics -> ShowS
Prelude.Show, forall x.
Rep GetQueryRuntimeStatistics x -> GetQueryRuntimeStatistics
forall x.
GetQueryRuntimeStatistics -> Rep GetQueryRuntimeStatistics x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetQueryRuntimeStatistics x -> GetQueryRuntimeStatistics
$cfrom :: forall x.
GetQueryRuntimeStatistics -> Rep GetQueryRuntimeStatistics x
Prelude.Generic)

-- |
-- Create a value of 'GetQueryRuntimeStatistics' 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:
--
-- 'queryExecutionId', 'getQueryRuntimeStatistics_queryExecutionId' - The unique ID of the query execution.
newGetQueryRuntimeStatistics ::
  -- | 'queryExecutionId'
  Prelude.Text ->
  GetQueryRuntimeStatistics
newGetQueryRuntimeStatistics :: Text -> GetQueryRuntimeStatistics
newGetQueryRuntimeStatistics Text
pQueryExecutionId_ =
  GetQueryRuntimeStatistics'
    { $sel:queryExecutionId:GetQueryRuntimeStatistics' :: Text
queryExecutionId =
        Text
pQueryExecutionId_
    }

-- | The unique ID of the query execution.
getQueryRuntimeStatistics_queryExecutionId :: Lens.Lens' GetQueryRuntimeStatistics Prelude.Text
getQueryRuntimeStatistics_queryExecutionId :: Lens' GetQueryRuntimeStatistics Text
getQueryRuntimeStatistics_queryExecutionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetQueryRuntimeStatistics' {Text
queryExecutionId :: Text
$sel:queryExecutionId:GetQueryRuntimeStatistics' :: GetQueryRuntimeStatistics -> Text
queryExecutionId} -> Text
queryExecutionId) (\s :: GetQueryRuntimeStatistics
s@GetQueryRuntimeStatistics' {} Text
a -> GetQueryRuntimeStatistics
s {$sel:queryExecutionId:GetQueryRuntimeStatistics' :: Text
queryExecutionId = Text
a} :: GetQueryRuntimeStatistics)

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

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

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

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

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

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

-- |
-- Create a value of 'GetQueryRuntimeStatisticsResponse' 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:
--
-- 'queryRuntimeStatistics', 'getQueryRuntimeStatisticsResponse_queryRuntimeStatistics' - Runtime statistics about the query execution.
--
-- 'httpStatus', 'getQueryRuntimeStatisticsResponse_httpStatus' - The response's http status code.
newGetQueryRuntimeStatisticsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetQueryRuntimeStatisticsResponse
newGetQueryRuntimeStatisticsResponse :: Int -> GetQueryRuntimeStatisticsResponse
newGetQueryRuntimeStatisticsResponse Int
pHttpStatus_ =
  GetQueryRuntimeStatisticsResponse'
    { $sel:queryRuntimeStatistics:GetQueryRuntimeStatisticsResponse' :: Maybe QueryRuntimeStatistics
queryRuntimeStatistics =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetQueryRuntimeStatisticsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Runtime statistics about the query execution.
getQueryRuntimeStatisticsResponse_queryRuntimeStatistics :: Lens.Lens' GetQueryRuntimeStatisticsResponse (Prelude.Maybe QueryRuntimeStatistics)
getQueryRuntimeStatisticsResponse_queryRuntimeStatistics :: Lens'
  GetQueryRuntimeStatisticsResponse (Maybe QueryRuntimeStatistics)
getQueryRuntimeStatisticsResponse_queryRuntimeStatistics = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetQueryRuntimeStatisticsResponse' {Maybe QueryRuntimeStatistics
queryRuntimeStatistics :: Maybe QueryRuntimeStatistics
$sel:queryRuntimeStatistics:GetQueryRuntimeStatisticsResponse' :: GetQueryRuntimeStatisticsResponse -> Maybe QueryRuntimeStatistics
queryRuntimeStatistics} -> Maybe QueryRuntimeStatistics
queryRuntimeStatistics) (\s :: GetQueryRuntimeStatisticsResponse
s@GetQueryRuntimeStatisticsResponse' {} Maybe QueryRuntimeStatistics
a -> GetQueryRuntimeStatisticsResponse
s {$sel:queryRuntimeStatistics:GetQueryRuntimeStatisticsResponse' :: Maybe QueryRuntimeStatistics
queryRuntimeStatistics = Maybe QueryRuntimeStatistics
a} :: GetQueryRuntimeStatisticsResponse)

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

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