{-# 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.Synthetics.Types.CanaryLastRun
-- 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.Synthetics.Types.CanaryLastRun 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
import Amazonka.Synthetics.Types.CanaryRun

-- | This structure contains information about the most recent run of a
-- single canary.
--
-- /See:/ 'newCanaryLastRun' smart constructor.
data CanaryLastRun = CanaryLastRun'
  { -- | The name of the canary.
    CanaryLastRun -> Maybe Text
canaryName :: Prelude.Maybe Prelude.Text,
    -- | The results from this canary\'s most recent run.
    CanaryLastRun -> Maybe CanaryRun
lastRun :: Prelude.Maybe CanaryRun
  }
  deriving (CanaryLastRun -> CanaryLastRun -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CanaryLastRun -> CanaryLastRun -> Bool
$c/= :: CanaryLastRun -> CanaryLastRun -> Bool
== :: CanaryLastRun -> CanaryLastRun -> Bool
$c== :: CanaryLastRun -> CanaryLastRun -> Bool
Prelude.Eq, ReadPrec [CanaryLastRun]
ReadPrec CanaryLastRun
Int -> ReadS CanaryLastRun
ReadS [CanaryLastRun]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CanaryLastRun]
$creadListPrec :: ReadPrec [CanaryLastRun]
readPrec :: ReadPrec CanaryLastRun
$creadPrec :: ReadPrec CanaryLastRun
readList :: ReadS [CanaryLastRun]
$creadList :: ReadS [CanaryLastRun]
readsPrec :: Int -> ReadS CanaryLastRun
$creadsPrec :: Int -> ReadS CanaryLastRun
Prelude.Read, Int -> CanaryLastRun -> ShowS
[CanaryLastRun] -> ShowS
CanaryLastRun -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CanaryLastRun] -> ShowS
$cshowList :: [CanaryLastRun] -> ShowS
show :: CanaryLastRun -> String
$cshow :: CanaryLastRun -> String
showsPrec :: Int -> CanaryLastRun -> ShowS
$cshowsPrec :: Int -> CanaryLastRun -> ShowS
Prelude.Show, forall x. Rep CanaryLastRun x -> CanaryLastRun
forall x. CanaryLastRun -> Rep CanaryLastRun x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CanaryLastRun x -> CanaryLastRun
$cfrom :: forall x. CanaryLastRun -> Rep CanaryLastRun x
Prelude.Generic)

-- |
-- Create a value of 'CanaryLastRun' 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:
--
-- 'canaryName', 'canaryLastRun_canaryName' - The name of the canary.
--
-- 'lastRun', 'canaryLastRun_lastRun' - The results from this canary\'s most recent run.
newCanaryLastRun ::
  CanaryLastRun
newCanaryLastRun :: CanaryLastRun
newCanaryLastRun =
  CanaryLastRun'
    { $sel:canaryName:CanaryLastRun' :: Maybe Text
canaryName = forall a. Maybe a
Prelude.Nothing,
      $sel:lastRun:CanaryLastRun' :: Maybe CanaryRun
lastRun = forall a. Maybe a
Prelude.Nothing
    }

-- | The name of the canary.
canaryLastRun_canaryName :: Lens.Lens' CanaryLastRun (Prelude.Maybe Prelude.Text)
canaryLastRun_canaryName :: Lens' CanaryLastRun (Maybe Text)
canaryLastRun_canaryName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CanaryLastRun' {Maybe Text
canaryName :: Maybe Text
$sel:canaryName:CanaryLastRun' :: CanaryLastRun -> Maybe Text
canaryName} -> Maybe Text
canaryName) (\s :: CanaryLastRun
s@CanaryLastRun' {} Maybe Text
a -> CanaryLastRun
s {$sel:canaryName:CanaryLastRun' :: Maybe Text
canaryName = Maybe Text
a} :: CanaryLastRun)

-- | The results from this canary\'s most recent run.
canaryLastRun_lastRun :: Lens.Lens' CanaryLastRun (Prelude.Maybe CanaryRun)
canaryLastRun_lastRun :: Lens' CanaryLastRun (Maybe CanaryRun)
canaryLastRun_lastRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CanaryLastRun' {Maybe CanaryRun
lastRun :: Maybe CanaryRun
$sel:lastRun:CanaryLastRun' :: CanaryLastRun -> Maybe CanaryRun
lastRun} -> Maybe CanaryRun
lastRun) (\s :: CanaryLastRun
s@CanaryLastRun' {} Maybe CanaryRun
a -> CanaryLastRun
s {$sel:lastRun:CanaryLastRun' :: Maybe CanaryRun
lastRun = Maybe CanaryRun
a} :: CanaryLastRun)

instance Data.FromJSON CanaryLastRun where
  parseJSON :: Value -> Parser CanaryLastRun
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"CanaryLastRun"
      ( \Object
x ->
          Maybe Text -> Maybe CanaryRun -> CanaryLastRun
CanaryLastRun'
            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
"CanaryName")
            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
"LastRun")
      )

instance Prelude.Hashable CanaryLastRun where
  hashWithSalt :: Int -> CanaryLastRun -> Int
hashWithSalt Int
_salt CanaryLastRun' {Maybe Text
Maybe CanaryRun
lastRun :: Maybe CanaryRun
canaryName :: Maybe Text
$sel:lastRun:CanaryLastRun' :: CanaryLastRun -> Maybe CanaryRun
$sel:canaryName:CanaryLastRun' :: CanaryLastRun -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
canaryName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CanaryRun
lastRun

instance Prelude.NFData CanaryLastRun where
  rnf :: CanaryLastRun -> ()
rnf CanaryLastRun' {Maybe Text
Maybe CanaryRun
lastRun :: Maybe CanaryRun
canaryName :: Maybe Text
$sel:lastRun:CanaryLastRun' :: CanaryLastRun -> Maybe CanaryRun
$sel:canaryName:CanaryLastRun' :: CanaryLastRun -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
canaryName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CanaryRun
lastRun