{-# 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.TimeStreamQuery.Types.QueryStatus
-- 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.TimeStreamQuery.Types.QueryStatus where

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 the status of the query, including progress and bytes
-- scanned.
--
-- /See:/ 'newQueryStatus' smart constructor.
data QueryStatus = QueryStatus'
  { -- | The amount of data scanned by the query in bytes that you will be
    -- charged for. This is a cumulative sum and represents the total amount of
    -- data that you will be charged for since the query was started. The
    -- charge is applied only once and is either applied when the query
    -- completes running or when the query is cancelled.
    QueryStatus -> Maybe Integer
cumulativeBytesMetered :: Prelude.Maybe Prelude.Integer,
    -- | The amount of data scanned by the query in bytes. This is a cumulative
    -- sum and represents the total amount of bytes scanned since the query was
    -- started.
    QueryStatus -> Maybe Integer
cumulativeBytesScanned :: Prelude.Maybe Prelude.Integer,
    -- | The progress of the query, expressed as a percentage.
    QueryStatus -> Maybe Double
progressPercentage :: Prelude.Maybe Prelude.Double
  }
  deriving (QueryStatus -> QueryStatus -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QueryStatus -> QueryStatus -> Bool
$c/= :: QueryStatus -> QueryStatus -> Bool
== :: QueryStatus -> QueryStatus -> Bool
$c== :: QueryStatus -> QueryStatus -> Bool
Prelude.Eq, ReadPrec [QueryStatus]
ReadPrec QueryStatus
Int -> ReadS QueryStatus
ReadS [QueryStatus]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [QueryStatus]
$creadListPrec :: ReadPrec [QueryStatus]
readPrec :: ReadPrec QueryStatus
$creadPrec :: ReadPrec QueryStatus
readList :: ReadS [QueryStatus]
$creadList :: ReadS [QueryStatus]
readsPrec :: Int -> ReadS QueryStatus
$creadsPrec :: Int -> ReadS QueryStatus
Prelude.Read, Int -> QueryStatus -> ShowS
[QueryStatus] -> ShowS
QueryStatus -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QueryStatus] -> ShowS
$cshowList :: [QueryStatus] -> ShowS
show :: QueryStatus -> String
$cshow :: QueryStatus -> String
showsPrec :: Int -> QueryStatus -> ShowS
$cshowsPrec :: Int -> QueryStatus -> ShowS
Prelude.Show, forall x. Rep QueryStatus x -> QueryStatus
forall x. QueryStatus -> Rep QueryStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep QueryStatus x -> QueryStatus
$cfrom :: forall x. QueryStatus -> Rep QueryStatus x
Prelude.Generic)

-- |
-- Create a value of 'QueryStatus' 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:
--
-- 'cumulativeBytesMetered', 'queryStatus_cumulativeBytesMetered' - The amount of data scanned by the query in bytes that you will be
-- charged for. This is a cumulative sum and represents the total amount of
-- data that you will be charged for since the query was started. The
-- charge is applied only once and is either applied when the query
-- completes running or when the query is cancelled.
--
-- 'cumulativeBytesScanned', 'queryStatus_cumulativeBytesScanned' - The amount of data scanned by the query in bytes. This is a cumulative
-- sum and represents the total amount of bytes scanned since the query was
-- started.
--
-- 'progressPercentage', 'queryStatus_progressPercentage' - The progress of the query, expressed as a percentage.
newQueryStatus ::
  QueryStatus
newQueryStatus :: QueryStatus
newQueryStatus =
  QueryStatus'
    { $sel:cumulativeBytesMetered:QueryStatus' :: Maybe Integer
cumulativeBytesMetered =
        forall a. Maybe a
Prelude.Nothing,
      $sel:cumulativeBytesScanned:QueryStatus' :: Maybe Integer
cumulativeBytesScanned = forall a. Maybe a
Prelude.Nothing,
      $sel:progressPercentage:QueryStatus' :: Maybe Double
progressPercentage = forall a. Maybe a
Prelude.Nothing
    }

-- | The amount of data scanned by the query in bytes that you will be
-- charged for. This is a cumulative sum and represents the total amount of
-- data that you will be charged for since the query was started. The
-- charge is applied only once and is either applied when the query
-- completes running or when the query is cancelled.
queryStatus_cumulativeBytesMetered :: Lens.Lens' QueryStatus (Prelude.Maybe Prelude.Integer)
queryStatus_cumulativeBytesMetered :: Lens' QueryStatus (Maybe Integer)
queryStatus_cumulativeBytesMetered = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryStatus' {Maybe Integer
cumulativeBytesMetered :: Maybe Integer
$sel:cumulativeBytesMetered:QueryStatus' :: QueryStatus -> Maybe Integer
cumulativeBytesMetered} -> Maybe Integer
cumulativeBytesMetered) (\s :: QueryStatus
s@QueryStatus' {} Maybe Integer
a -> QueryStatus
s {$sel:cumulativeBytesMetered:QueryStatus' :: Maybe Integer
cumulativeBytesMetered = Maybe Integer
a} :: QueryStatus)

-- | The amount of data scanned by the query in bytes. This is a cumulative
-- sum and represents the total amount of bytes scanned since the query was
-- started.
queryStatus_cumulativeBytesScanned :: Lens.Lens' QueryStatus (Prelude.Maybe Prelude.Integer)
queryStatus_cumulativeBytesScanned :: Lens' QueryStatus (Maybe Integer)
queryStatus_cumulativeBytesScanned = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryStatus' {Maybe Integer
cumulativeBytesScanned :: Maybe Integer
$sel:cumulativeBytesScanned:QueryStatus' :: QueryStatus -> Maybe Integer
cumulativeBytesScanned} -> Maybe Integer
cumulativeBytesScanned) (\s :: QueryStatus
s@QueryStatus' {} Maybe Integer
a -> QueryStatus
s {$sel:cumulativeBytesScanned:QueryStatus' :: Maybe Integer
cumulativeBytesScanned = Maybe Integer
a} :: QueryStatus)

-- | The progress of the query, expressed as a percentage.
queryStatus_progressPercentage :: Lens.Lens' QueryStatus (Prelude.Maybe Prelude.Double)
queryStatus_progressPercentage :: Lens' QueryStatus (Maybe Double)
queryStatus_progressPercentage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryStatus' {Maybe Double
progressPercentage :: Maybe Double
$sel:progressPercentage:QueryStatus' :: QueryStatus -> Maybe Double
progressPercentage} -> Maybe Double
progressPercentage) (\s :: QueryStatus
s@QueryStatus' {} Maybe Double
a -> QueryStatus
s {$sel:progressPercentage:QueryStatus' :: Maybe Double
progressPercentage = Maybe Double
a} :: QueryStatus)

instance Data.FromJSON QueryStatus where
  parseJSON :: Value -> Parser QueryStatus
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"QueryStatus"
      ( \Object
x ->
          Maybe Integer -> Maybe Integer -> Maybe Double -> QueryStatus
QueryStatus'
            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
"CumulativeBytesMetered")
            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
"CumulativeBytesScanned")
            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
"ProgressPercentage")
      )

instance Prelude.Hashable QueryStatus where
  hashWithSalt :: Int -> QueryStatus -> Int
hashWithSalt Int
_salt QueryStatus' {Maybe Double
Maybe Integer
progressPercentage :: Maybe Double
cumulativeBytesScanned :: Maybe Integer
cumulativeBytesMetered :: Maybe Integer
$sel:progressPercentage:QueryStatus' :: QueryStatus -> Maybe Double
$sel:cumulativeBytesScanned:QueryStatus' :: QueryStatus -> Maybe Integer
$sel:cumulativeBytesMetered:QueryStatus' :: QueryStatus -> Maybe Integer
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
cumulativeBytesMetered
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
cumulativeBytesScanned
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Double
progressPercentage

instance Prelude.NFData QueryStatus where
  rnf :: QueryStatus -> ()
rnf QueryStatus' {Maybe Double
Maybe Integer
progressPercentage :: Maybe Double
cumulativeBytesScanned :: Maybe Integer
cumulativeBytesMetered :: Maybe Integer
$sel:progressPercentage:QueryStatus' :: QueryStatus -> Maybe Double
$sel:cumulativeBytesScanned:QueryStatus' :: QueryStatus -> Maybe Integer
$sel:cumulativeBytesMetered:QueryStatus' :: QueryStatus -> Maybe Integer
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
cumulativeBytesMetered
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
cumulativeBytesScanned
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Double
progressPercentage