{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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.Types.QueryExecution
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.Athena.Types.QueryExecution where

import Amazonka.Athena.Types.EngineVersion
import Amazonka.Athena.Types.QueryExecutionContext
import Amazonka.Athena.Types.QueryExecutionStatistics
import Amazonka.Athena.Types.QueryExecutionStatus
import Amazonka.Athena.Types.ResultConfiguration
import Amazonka.Athena.Types.ResultReuseConfiguration
import Amazonka.Athena.Types.StatementType
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

-- | Information about a single instance of a query execution.
--
-- /See:/ 'newQueryExecution' smart constructor.
data QueryExecution = QueryExecution'
  { -- | The engine version that executed the query.
    QueryExecution -> Maybe EngineVersion
engineVersion :: Prelude.Maybe EngineVersion,
    -- | A list of values for the parameters in a query. The values are applied
    -- sequentially to the parameters in the query in the order in which the
    -- parameters occur.
    QueryExecution -> Maybe (NonEmpty Text)
executionParameters :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | The SQL query statements which the query execution ran.
    QueryExecution -> Maybe Text
query :: Prelude.Maybe Prelude.Text,
    -- | The database in which the query execution occurred.
    QueryExecution -> Maybe QueryExecutionContext
queryExecutionContext :: Prelude.Maybe QueryExecutionContext,
    -- | The unique identifier for each query execution.
    QueryExecution -> Maybe Text
queryExecutionId :: Prelude.Maybe Prelude.Text,
    -- | The location in Amazon S3 where query results were stored and the
    -- encryption option, if any, used for query results. These are known as
    -- \"client-side settings\". If workgroup settings override client-side
    -- settings, then the query uses the location for the query results and the
    -- encryption configuration that are specified for the workgroup.
    QueryExecution -> Maybe ResultConfiguration
resultConfiguration :: Prelude.Maybe ResultConfiguration,
    -- | Specifies the query result reuse behavior that was used for the query.
    QueryExecution -> Maybe ResultReuseConfiguration
resultReuseConfiguration :: Prelude.Maybe ResultReuseConfiguration,
    -- | The type of query statement that was run. @DDL@ indicates DDL query
    -- statements. @DML@ indicates DML (Data Manipulation Language) query
    -- statements, such as @CREATE TABLE AS SELECT@. @UTILITY@ indicates query
    -- statements other than DDL and DML, such as @SHOW CREATE TABLE@, or
    -- @DESCRIBE TABLE@.
    QueryExecution -> Maybe StatementType
statementType :: Prelude.Maybe StatementType,
    -- | Query execution statistics, such as the amount of data scanned, the
    -- amount of time that the query took to process, and the type of statement
    -- that was run.
    QueryExecution -> Maybe QueryExecutionStatistics
statistics :: Prelude.Maybe QueryExecutionStatistics,
    -- | The completion date, current state, submission time, and state change
    -- reason (if applicable) for the query execution.
    QueryExecution -> Maybe QueryExecutionStatus
status :: Prelude.Maybe QueryExecutionStatus,
    -- | The name of the workgroup in which the query ran.
    QueryExecution -> Maybe Text
workGroup :: Prelude.Maybe Prelude.Text
  }
  deriving (QueryExecution -> QueryExecution -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QueryExecution -> QueryExecution -> Bool
$c/= :: QueryExecution -> QueryExecution -> Bool
== :: QueryExecution -> QueryExecution -> Bool
$c== :: QueryExecution -> QueryExecution -> Bool
Prelude.Eq, ReadPrec [QueryExecution]
ReadPrec QueryExecution
Int -> ReadS QueryExecution
ReadS [QueryExecution]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [QueryExecution]
$creadListPrec :: ReadPrec [QueryExecution]
readPrec :: ReadPrec QueryExecution
$creadPrec :: ReadPrec QueryExecution
readList :: ReadS [QueryExecution]
$creadList :: ReadS [QueryExecution]
readsPrec :: Int -> ReadS QueryExecution
$creadsPrec :: Int -> ReadS QueryExecution
Prelude.Read, Int -> QueryExecution -> ShowS
[QueryExecution] -> ShowS
QueryExecution -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QueryExecution] -> ShowS
$cshowList :: [QueryExecution] -> ShowS
show :: QueryExecution -> String
$cshow :: QueryExecution -> String
showsPrec :: Int -> QueryExecution -> ShowS
$cshowsPrec :: Int -> QueryExecution -> ShowS
Prelude.Show, forall x. Rep QueryExecution x -> QueryExecution
forall x. QueryExecution -> Rep QueryExecution x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep QueryExecution x -> QueryExecution
$cfrom :: forall x. QueryExecution -> Rep QueryExecution x
Prelude.Generic)

-- |
-- Create a value of 'QueryExecution' 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:
--
-- 'engineVersion', 'queryExecution_engineVersion' - The engine version that executed the query.
--
-- 'executionParameters', 'queryExecution_executionParameters' - A list of values for the parameters in a query. The values are applied
-- sequentially to the parameters in the query in the order in which the
-- parameters occur.
--
-- 'query', 'queryExecution_query' - The SQL query statements which the query execution ran.
--
-- 'queryExecutionContext', 'queryExecution_queryExecutionContext' - The database in which the query execution occurred.
--
-- 'queryExecutionId', 'queryExecution_queryExecutionId' - The unique identifier for each query execution.
--
-- 'resultConfiguration', 'queryExecution_resultConfiguration' - The location in Amazon S3 where query results were stored and the
-- encryption option, if any, used for query results. These are known as
-- \"client-side settings\". If workgroup settings override client-side
-- settings, then the query uses the location for the query results and the
-- encryption configuration that are specified for the workgroup.
--
-- 'resultReuseConfiguration', 'queryExecution_resultReuseConfiguration' - Specifies the query result reuse behavior that was used for the query.
--
-- 'statementType', 'queryExecution_statementType' - The type of query statement that was run. @DDL@ indicates DDL query
-- statements. @DML@ indicates DML (Data Manipulation Language) query
-- statements, such as @CREATE TABLE AS SELECT@. @UTILITY@ indicates query
-- statements other than DDL and DML, such as @SHOW CREATE TABLE@, or
-- @DESCRIBE TABLE@.
--
-- 'statistics', 'queryExecution_statistics' - Query execution statistics, such as the amount of data scanned, the
-- amount of time that the query took to process, and the type of statement
-- that was run.
--
-- 'status', 'queryExecution_status' - The completion date, current state, submission time, and state change
-- reason (if applicable) for the query execution.
--
-- 'workGroup', 'queryExecution_workGroup' - The name of the workgroup in which the query ran.
newQueryExecution ::
  QueryExecution
newQueryExecution :: QueryExecution
newQueryExecution =
  QueryExecution'
    { $sel:engineVersion:QueryExecution' :: Maybe EngineVersion
engineVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:executionParameters:QueryExecution' :: Maybe (NonEmpty Text)
executionParameters = forall a. Maybe a
Prelude.Nothing,
      $sel:query:QueryExecution' :: Maybe Text
query = forall a. Maybe a
Prelude.Nothing,
      $sel:queryExecutionContext:QueryExecution' :: Maybe QueryExecutionContext
queryExecutionContext = forall a. Maybe a
Prelude.Nothing,
      $sel:queryExecutionId:QueryExecution' :: Maybe Text
queryExecutionId = forall a. Maybe a
Prelude.Nothing,
      $sel:resultConfiguration:QueryExecution' :: Maybe ResultConfiguration
resultConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:resultReuseConfiguration:QueryExecution' :: Maybe ResultReuseConfiguration
resultReuseConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:statementType:QueryExecution' :: Maybe StatementType
statementType = forall a. Maybe a
Prelude.Nothing,
      $sel:statistics:QueryExecution' :: Maybe QueryExecutionStatistics
statistics = forall a. Maybe a
Prelude.Nothing,
      $sel:status:QueryExecution' :: Maybe QueryExecutionStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:workGroup:QueryExecution' :: Maybe Text
workGroup = forall a. Maybe a
Prelude.Nothing
    }

-- | The engine version that executed the query.
queryExecution_engineVersion :: Lens.Lens' QueryExecution (Prelude.Maybe EngineVersion)
queryExecution_engineVersion :: Lens' QueryExecution (Maybe EngineVersion)
queryExecution_engineVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryExecution' {Maybe EngineVersion
engineVersion :: Maybe EngineVersion
$sel:engineVersion:QueryExecution' :: QueryExecution -> Maybe EngineVersion
engineVersion} -> Maybe EngineVersion
engineVersion) (\s :: QueryExecution
s@QueryExecution' {} Maybe EngineVersion
a -> QueryExecution
s {$sel:engineVersion:QueryExecution' :: Maybe EngineVersion
engineVersion = Maybe EngineVersion
a} :: QueryExecution)

-- | A list of values for the parameters in a query. The values are applied
-- sequentially to the parameters in the query in the order in which the
-- parameters occur.
queryExecution_executionParameters :: Lens.Lens' QueryExecution (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
queryExecution_executionParameters :: Lens' QueryExecution (Maybe (NonEmpty Text))
queryExecution_executionParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryExecution' {Maybe (NonEmpty Text)
executionParameters :: Maybe (NonEmpty Text)
$sel:executionParameters:QueryExecution' :: QueryExecution -> Maybe (NonEmpty Text)
executionParameters} -> Maybe (NonEmpty Text)
executionParameters) (\s :: QueryExecution
s@QueryExecution' {} Maybe (NonEmpty Text)
a -> QueryExecution
s {$sel:executionParameters:QueryExecution' :: Maybe (NonEmpty Text)
executionParameters = Maybe (NonEmpty Text)
a} :: QueryExecution) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The SQL query statements which the query execution ran.
queryExecution_query :: Lens.Lens' QueryExecution (Prelude.Maybe Prelude.Text)
queryExecution_query :: Lens' QueryExecution (Maybe Text)
queryExecution_query = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryExecution' {Maybe Text
query :: Maybe Text
$sel:query:QueryExecution' :: QueryExecution -> Maybe Text
query} -> Maybe Text
query) (\s :: QueryExecution
s@QueryExecution' {} Maybe Text
a -> QueryExecution
s {$sel:query:QueryExecution' :: Maybe Text
query = Maybe Text
a} :: QueryExecution)

-- | The database in which the query execution occurred.
queryExecution_queryExecutionContext :: Lens.Lens' QueryExecution (Prelude.Maybe QueryExecutionContext)
queryExecution_queryExecutionContext :: Lens' QueryExecution (Maybe QueryExecutionContext)
queryExecution_queryExecutionContext = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryExecution' {Maybe QueryExecutionContext
queryExecutionContext :: Maybe QueryExecutionContext
$sel:queryExecutionContext:QueryExecution' :: QueryExecution -> Maybe QueryExecutionContext
queryExecutionContext} -> Maybe QueryExecutionContext
queryExecutionContext) (\s :: QueryExecution
s@QueryExecution' {} Maybe QueryExecutionContext
a -> QueryExecution
s {$sel:queryExecutionContext:QueryExecution' :: Maybe QueryExecutionContext
queryExecutionContext = Maybe QueryExecutionContext
a} :: QueryExecution)

-- | The unique identifier for each query execution.
queryExecution_queryExecutionId :: Lens.Lens' QueryExecution (Prelude.Maybe Prelude.Text)
queryExecution_queryExecutionId :: Lens' QueryExecution (Maybe Text)
queryExecution_queryExecutionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryExecution' {Maybe Text
queryExecutionId :: Maybe Text
$sel:queryExecutionId:QueryExecution' :: QueryExecution -> Maybe Text
queryExecutionId} -> Maybe Text
queryExecutionId) (\s :: QueryExecution
s@QueryExecution' {} Maybe Text
a -> QueryExecution
s {$sel:queryExecutionId:QueryExecution' :: Maybe Text
queryExecutionId = Maybe Text
a} :: QueryExecution)

-- | The location in Amazon S3 where query results were stored and the
-- encryption option, if any, used for query results. These are known as
-- \"client-side settings\". If workgroup settings override client-side
-- settings, then the query uses the location for the query results and the
-- encryption configuration that are specified for the workgroup.
queryExecution_resultConfiguration :: Lens.Lens' QueryExecution (Prelude.Maybe ResultConfiguration)
queryExecution_resultConfiguration :: Lens' QueryExecution (Maybe ResultConfiguration)
queryExecution_resultConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryExecution' {Maybe ResultConfiguration
resultConfiguration :: Maybe ResultConfiguration
$sel:resultConfiguration:QueryExecution' :: QueryExecution -> Maybe ResultConfiguration
resultConfiguration} -> Maybe ResultConfiguration
resultConfiguration) (\s :: QueryExecution
s@QueryExecution' {} Maybe ResultConfiguration
a -> QueryExecution
s {$sel:resultConfiguration:QueryExecution' :: Maybe ResultConfiguration
resultConfiguration = Maybe ResultConfiguration
a} :: QueryExecution)

-- | Specifies the query result reuse behavior that was used for the query.
queryExecution_resultReuseConfiguration :: Lens.Lens' QueryExecution (Prelude.Maybe ResultReuseConfiguration)
queryExecution_resultReuseConfiguration :: Lens' QueryExecution (Maybe ResultReuseConfiguration)
queryExecution_resultReuseConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryExecution' {Maybe ResultReuseConfiguration
resultReuseConfiguration :: Maybe ResultReuseConfiguration
$sel:resultReuseConfiguration:QueryExecution' :: QueryExecution -> Maybe ResultReuseConfiguration
resultReuseConfiguration} -> Maybe ResultReuseConfiguration
resultReuseConfiguration) (\s :: QueryExecution
s@QueryExecution' {} Maybe ResultReuseConfiguration
a -> QueryExecution
s {$sel:resultReuseConfiguration:QueryExecution' :: Maybe ResultReuseConfiguration
resultReuseConfiguration = Maybe ResultReuseConfiguration
a} :: QueryExecution)

-- | The type of query statement that was run. @DDL@ indicates DDL query
-- statements. @DML@ indicates DML (Data Manipulation Language) query
-- statements, such as @CREATE TABLE AS SELECT@. @UTILITY@ indicates query
-- statements other than DDL and DML, such as @SHOW CREATE TABLE@, or
-- @DESCRIBE TABLE@.
queryExecution_statementType :: Lens.Lens' QueryExecution (Prelude.Maybe StatementType)
queryExecution_statementType :: Lens' QueryExecution (Maybe StatementType)
queryExecution_statementType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryExecution' {Maybe StatementType
statementType :: Maybe StatementType
$sel:statementType:QueryExecution' :: QueryExecution -> Maybe StatementType
statementType} -> Maybe StatementType
statementType) (\s :: QueryExecution
s@QueryExecution' {} Maybe StatementType
a -> QueryExecution
s {$sel:statementType:QueryExecution' :: Maybe StatementType
statementType = Maybe StatementType
a} :: QueryExecution)

-- | Query execution statistics, such as the amount of data scanned, the
-- amount of time that the query took to process, and the type of statement
-- that was run.
queryExecution_statistics :: Lens.Lens' QueryExecution (Prelude.Maybe QueryExecutionStatistics)
queryExecution_statistics :: Lens' QueryExecution (Maybe QueryExecutionStatistics)
queryExecution_statistics = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryExecution' {Maybe QueryExecutionStatistics
statistics :: Maybe QueryExecutionStatistics
$sel:statistics:QueryExecution' :: QueryExecution -> Maybe QueryExecutionStatistics
statistics} -> Maybe QueryExecutionStatistics
statistics) (\s :: QueryExecution
s@QueryExecution' {} Maybe QueryExecutionStatistics
a -> QueryExecution
s {$sel:statistics:QueryExecution' :: Maybe QueryExecutionStatistics
statistics = Maybe QueryExecutionStatistics
a} :: QueryExecution)

-- | The completion date, current state, submission time, and state change
-- reason (if applicable) for the query execution.
queryExecution_status :: Lens.Lens' QueryExecution (Prelude.Maybe QueryExecutionStatus)
queryExecution_status :: Lens' QueryExecution (Maybe QueryExecutionStatus)
queryExecution_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryExecution' {Maybe QueryExecutionStatus
status :: Maybe QueryExecutionStatus
$sel:status:QueryExecution' :: QueryExecution -> Maybe QueryExecutionStatus
status} -> Maybe QueryExecutionStatus
status) (\s :: QueryExecution
s@QueryExecution' {} Maybe QueryExecutionStatus
a -> QueryExecution
s {$sel:status:QueryExecution' :: Maybe QueryExecutionStatus
status = Maybe QueryExecutionStatus
a} :: QueryExecution)

-- | The name of the workgroup in which the query ran.
queryExecution_workGroup :: Lens.Lens' QueryExecution (Prelude.Maybe Prelude.Text)
queryExecution_workGroup :: Lens' QueryExecution (Maybe Text)
queryExecution_workGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryExecution' {Maybe Text
workGroup :: Maybe Text
$sel:workGroup:QueryExecution' :: QueryExecution -> Maybe Text
workGroup} -> Maybe Text
workGroup) (\s :: QueryExecution
s@QueryExecution' {} Maybe Text
a -> QueryExecution
s {$sel:workGroup:QueryExecution' :: Maybe Text
workGroup = Maybe Text
a} :: QueryExecution)

instance Data.FromJSON QueryExecution where
  parseJSON :: Value -> Parser QueryExecution
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"QueryExecution"
      ( \Object
x ->
          Maybe EngineVersion
-> Maybe (NonEmpty Text)
-> Maybe Text
-> Maybe QueryExecutionContext
-> Maybe Text
-> Maybe ResultConfiguration
-> Maybe ResultReuseConfiguration
-> Maybe StatementType
-> Maybe QueryExecutionStatistics
-> Maybe QueryExecutionStatus
-> Maybe Text
-> QueryExecution
QueryExecution'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"EngineVersion")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ExecutionParameters")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Query")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"QueryExecutionContext")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"QueryExecutionId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ResultConfiguration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ResultReuseConfiguration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"StatementType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Statistics")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Status")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"WorkGroup")
      )

instance Prelude.Hashable QueryExecution where
  hashWithSalt :: Int -> QueryExecution -> Int
hashWithSalt Int
_salt QueryExecution' {Maybe (NonEmpty Text)
Maybe Text
Maybe EngineVersion
Maybe QueryExecutionContext
Maybe QueryExecutionStatus
Maybe ResultReuseConfiguration
Maybe QueryExecutionStatistics
Maybe ResultConfiguration
Maybe StatementType
workGroup :: Maybe Text
status :: Maybe QueryExecutionStatus
statistics :: Maybe QueryExecutionStatistics
statementType :: Maybe StatementType
resultReuseConfiguration :: Maybe ResultReuseConfiguration
resultConfiguration :: Maybe ResultConfiguration
queryExecutionId :: Maybe Text
queryExecutionContext :: Maybe QueryExecutionContext
query :: Maybe Text
executionParameters :: Maybe (NonEmpty Text)
engineVersion :: Maybe EngineVersion
$sel:workGroup:QueryExecution' :: QueryExecution -> Maybe Text
$sel:status:QueryExecution' :: QueryExecution -> Maybe QueryExecutionStatus
$sel:statistics:QueryExecution' :: QueryExecution -> Maybe QueryExecutionStatistics
$sel:statementType:QueryExecution' :: QueryExecution -> Maybe StatementType
$sel:resultReuseConfiguration:QueryExecution' :: QueryExecution -> Maybe ResultReuseConfiguration
$sel:resultConfiguration:QueryExecution' :: QueryExecution -> Maybe ResultConfiguration
$sel:queryExecutionId:QueryExecution' :: QueryExecution -> Maybe Text
$sel:queryExecutionContext:QueryExecution' :: QueryExecution -> Maybe QueryExecutionContext
$sel:query:QueryExecution' :: QueryExecution -> Maybe Text
$sel:executionParameters:QueryExecution' :: QueryExecution -> Maybe (NonEmpty Text)
$sel:engineVersion:QueryExecution' :: QueryExecution -> Maybe EngineVersion
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EngineVersion
engineVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Text)
executionParameters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
query
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe QueryExecutionContext
queryExecutionContext
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
queryExecutionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ResultConfiguration
resultConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ResultReuseConfiguration
resultReuseConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe StatementType
statementType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe QueryExecutionStatistics
statistics
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe QueryExecutionStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
workGroup

instance Prelude.NFData QueryExecution where
  rnf :: QueryExecution -> ()
rnf QueryExecution' {Maybe (NonEmpty Text)
Maybe Text
Maybe EngineVersion
Maybe QueryExecutionContext
Maybe QueryExecutionStatus
Maybe ResultReuseConfiguration
Maybe QueryExecutionStatistics
Maybe ResultConfiguration
Maybe StatementType
workGroup :: Maybe Text
status :: Maybe QueryExecutionStatus
statistics :: Maybe QueryExecutionStatistics
statementType :: Maybe StatementType
resultReuseConfiguration :: Maybe ResultReuseConfiguration
resultConfiguration :: Maybe ResultConfiguration
queryExecutionId :: Maybe Text
queryExecutionContext :: Maybe QueryExecutionContext
query :: Maybe Text
executionParameters :: Maybe (NonEmpty Text)
engineVersion :: Maybe EngineVersion
$sel:workGroup:QueryExecution' :: QueryExecution -> Maybe Text
$sel:status:QueryExecution' :: QueryExecution -> Maybe QueryExecutionStatus
$sel:statistics:QueryExecution' :: QueryExecution -> Maybe QueryExecutionStatistics
$sel:statementType:QueryExecution' :: QueryExecution -> Maybe StatementType
$sel:resultReuseConfiguration:QueryExecution' :: QueryExecution -> Maybe ResultReuseConfiguration
$sel:resultConfiguration:QueryExecution' :: QueryExecution -> Maybe ResultConfiguration
$sel:queryExecutionId:QueryExecution' :: QueryExecution -> Maybe Text
$sel:queryExecutionContext:QueryExecution' :: QueryExecution -> Maybe QueryExecutionContext
$sel:query:QueryExecution' :: QueryExecution -> Maybe Text
$sel:executionParameters:QueryExecution' :: QueryExecution -> Maybe (NonEmpty Text)
$sel:engineVersion:QueryExecution' :: QueryExecution -> Maybe EngineVersion
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe EngineVersion
engineVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Text)
executionParameters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
query
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe QueryExecutionContext
queryExecutionContext
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
queryExecutionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ResultConfiguration
resultConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ResultReuseConfiguration
resultReuseConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe StatementType
statementType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe QueryExecutionStatistics
statistics
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe QueryExecutionStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
workGroup