{-# 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.CodeGuruProfiler.Types.AggregatedProfileTime
-- 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.CodeGuruProfiler.Types.AggregatedProfileTime where

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

-- | Specifies the aggregation period and aggregation start time for an
-- aggregated profile. An aggregated profile is used to collect posted
-- agent profiles during an aggregation period. There are three possible
-- aggregation periods (1 day, 1 hour, or 5 minutes).
--
-- /See:/ 'newAggregatedProfileTime' smart constructor.
data AggregatedProfileTime = AggregatedProfileTime'
  { -- | The aggregation period. This indicates the period during which an
    -- aggregation profile collects posted agent profiles for a profiling
    -- group. Use one of three valid durations that are specified using the ISO
    -- 8601 format.
    --
    -- -   @P1D@ — 1 day
    --
    -- -   @PT1H@ — 1 hour
    --
    -- -   @PT5M@ — 5 minutes
    AggregatedProfileTime -> Maybe AggregationPeriod
period :: Prelude.Maybe AggregationPeriod,
    -- | The time that aggregation of posted agent profiles for a profiling group
    -- starts. The aggregation profile contains profiles posted by the agent
    -- starting at this time for an aggregation period specified by the
    -- @period@ property of the @AggregatedProfileTime@ object.
    --
    -- Specify @start@ using the ISO 8601 format. For example,
    -- 2020-06-01T13:15:02.001Z represents 1 millisecond past June 1, 2020
    -- 1:15:02 PM UTC.
    AggregatedProfileTime -> Maybe ISO8601
start :: Prelude.Maybe Data.ISO8601
  }
  deriving (AggregatedProfileTime -> AggregatedProfileTime -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AggregatedProfileTime -> AggregatedProfileTime -> Bool
$c/= :: AggregatedProfileTime -> AggregatedProfileTime -> Bool
== :: AggregatedProfileTime -> AggregatedProfileTime -> Bool
$c== :: AggregatedProfileTime -> AggregatedProfileTime -> Bool
Prelude.Eq, ReadPrec [AggregatedProfileTime]
ReadPrec AggregatedProfileTime
Int -> ReadS AggregatedProfileTime
ReadS [AggregatedProfileTime]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AggregatedProfileTime]
$creadListPrec :: ReadPrec [AggregatedProfileTime]
readPrec :: ReadPrec AggregatedProfileTime
$creadPrec :: ReadPrec AggregatedProfileTime
readList :: ReadS [AggregatedProfileTime]
$creadList :: ReadS [AggregatedProfileTime]
readsPrec :: Int -> ReadS AggregatedProfileTime
$creadsPrec :: Int -> ReadS AggregatedProfileTime
Prelude.Read, Int -> AggregatedProfileTime -> ShowS
[AggregatedProfileTime] -> ShowS
AggregatedProfileTime -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AggregatedProfileTime] -> ShowS
$cshowList :: [AggregatedProfileTime] -> ShowS
show :: AggregatedProfileTime -> String
$cshow :: AggregatedProfileTime -> String
showsPrec :: Int -> AggregatedProfileTime -> ShowS
$cshowsPrec :: Int -> AggregatedProfileTime -> ShowS
Prelude.Show, forall x. Rep AggregatedProfileTime x -> AggregatedProfileTime
forall x. AggregatedProfileTime -> Rep AggregatedProfileTime x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AggregatedProfileTime x -> AggregatedProfileTime
$cfrom :: forall x. AggregatedProfileTime -> Rep AggregatedProfileTime x
Prelude.Generic)

-- |
-- Create a value of 'AggregatedProfileTime' 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:
--
-- 'period', 'aggregatedProfileTime_period' - The aggregation period. This indicates the period during which an
-- aggregation profile collects posted agent profiles for a profiling
-- group. Use one of three valid durations that are specified using the ISO
-- 8601 format.
--
-- -   @P1D@ — 1 day
--
-- -   @PT1H@ — 1 hour
--
-- -   @PT5M@ — 5 minutes
--
-- 'start', 'aggregatedProfileTime_start' - The time that aggregation of posted agent profiles for a profiling group
-- starts. The aggregation profile contains profiles posted by the agent
-- starting at this time for an aggregation period specified by the
-- @period@ property of the @AggregatedProfileTime@ object.
--
-- Specify @start@ using the ISO 8601 format. For example,
-- 2020-06-01T13:15:02.001Z represents 1 millisecond past June 1, 2020
-- 1:15:02 PM UTC.
newAggregatedProfileTime ::
  AggregatedProfileTime
newAggregatedProfileTime :: AggregatedProfileTime
newAggregatedProfileTime =
  AggregatedProfileTime'
    { $sel:period:AggregatedProfileTime' :: Maybe AggregationPeriod
period = forall a. Maybe a
Prelude.Nothing,
      $sel:start:AggregatedProfileTime' :: Maybe ISO8601
start = forall a. Maybe a
Prelude.Nothing
    }

-- | The aggregation period. This indicates the period during which an
-- aggregation profile collects posted agent profiles for a profiling
-- group. Use one of three valid durations that are specified using the ISO
-- 8601 format.
--
-- -   @P1D@ — 1 day
--
-- -   @PT1H@ — 1 hour
--
-- -   @PT5M@ — 5 minutes
aggregatedProfileTime_period :: Lens.Lens' AggregatedProfileTime (Prelude.Maybe AggregationPeriod)
aggregatedProfileTime_period :: Lens' AggregatedProfileTime (Maybe AggregationPeriod)
aggregatedProfileTime_period = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AggregatedProfileTime' {Maybe AggregationPeriod
period :: Maybe AggregationPeriod
$sel:period:AggregatedProfileTime' :: AggregatedProfileTime -> Maybe AggregationPeriod
period} -> Maybe AggregationPeriod
period) (\s :: AggregatedProfileTime
s@AggregatedProfileTime' {} Maybe AggregationPeriod
a -> AggregatedProfileTime
s {$sel:period:AggregatedProfileTime' :: Maybe AggregationPeriod
period = Maybe AggregationPeriod
a} :: AggregatedProfileTime)

-- | The time that aggregation of posted agent profiles for a profiling group
-- starts. The aggregation profile contains profiles posted by the agent
-- starting at this time for an aggregation period specified by the
-- @period@ property of the @AggregatedProfileTime@ object.
--
-- Specify @start@ using the ISO 8601 format. For example,
-- 2020-06-01T13:15:02.001Z represents 1 millisecond past June 1, 2020
-- 1:15:02 PM UTC.
aggregatedProfileTime_start :: Lens.Lens' AggregatedProfileTime (Prelude.Maybe Prelude.UTCTime)
aggregatedProfileTime_start :: Lens' AggregatedProfileTime (Maybe UTCTime)
aggregatedProfileTime_start = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AggregatedProfileTime' {Maybe ISO8601
start :: Maybe ISO8601
$sel:start:AggregatedProfileTime' :: AggregatedProfileTime -> Maybe ISO8601
start} -> Maybe ISO8601
start) (\s :: AggregatedProfileTime
s@AggregatedProfileTime' {} Maybe ISO8601
a -> AggregatedProfileTime
s {$sel:start:AggregatedProfileTime' :: Maybe ISO8601
start = Maybe ISO8601
a} :: AggregatedProfileTime) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

instance Data.FromJSON AggregatedProfileTime where
  parseJSON :: Value -> Parser AggregatedProfileTime
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"AggregatedProfileTime"
      ( \Object
x ->
          Maybe AggregationPeriod -> Maybe ISO8601 -> AggregatedProfileTime
AggregatedProfileTime'
            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
"period")
            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
"start")
      )

instance Prelude.Hashable AggregatedProfileTime where
  hashWithSalt :: Int -> AggregatedProfileTime -> Int
hashWithSalt Int
_salt AggregatedProfileTime' {Maybe ISO8601
Maybe AggregationPeriod
start :: Maybe ISO8601
period :: Maybe AggregationPeriod
$sel:start:AggregatedProfileTime' :: AggregatedProfileTime -> Maybe ISO8601
$sel:period:AggregatedProfileTime' :: AggregatedProfileTime -> Maybe AggregationPeriod
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AggregationPeriod
period
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
start

instance Prelude.NFData AggregatedProfileTime where
  rnf :: AggregatedProfileTime -> ()
rnf AggregatedProfileTime' {Maybe ISO8601
Maybe AggregationPeriod
start :: Maybe ISO8601
period :: Maybe AggregationPeriod
$sel:start:AggregatedProfileTime' :: AggregatedProfileTime -> Maybe ISO8601
$sel:period:AggregatedProfileTime' :: AggregatedProfileTime -> Maybe AggregationPeriod
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AggregationPeriod
period seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
start