{-# 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.AWSHealth.Types.EventType
-- 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.AWSHealth.Types.EventType where

import Amazonka.AWSHealth.Types.EventTypeCategory
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

-- | Contains the metadata about a type of event that is reported by Health.
-- The @EventType@ shows the category, service, and the event type code of
-- the event. For example, an @issue@ might be the category, @EC2@ the
-- service, and @AWS_EC2_SYSTEM_MAINTENANCE_EVENT@ the event type code.
--
-- You can use the
-- <https://docs.aws.amazon.com/health/latest/APIReference/API_DescribeEventTypes.html DescribeEventTypes>
-- API operation to return this information about an event.
--
-- You can also use the Amazon CloudWatch Events console to create a rule
-- so that you can get notified or take action when Health delivers a
-- specific event to your Amazon Web Services account. For more
-- information, see
-- <https://docs.aws.amazon.com/health/latest/ug/cloudwatch-events-health.html Monitor for Health events with Amazon CloudWatch Events>
-- in the /Health User Guide/.
--
-- /See:/ 'newEventType' smart constructor.
data EventType = EventType'
  { -- | A list of event type category codes. Possible values are @issue@,
    -- @accountNotification@, or @scheduledChange@. Currently, the
    -- @investigation@ value isn\'t supported at this time.
    EventType -> Maybe EventTypeCategory
category :: Prelude.Maybe EventTypeCategory,
    -- | The unique identifier for the event type. The format is
    -- @AWS_@/@SERVICE@/@_@/@DESCRIPTION@/@ @; for example,
    -- @AWS_EC2_SYSTEM_MAINTENANCE_EVENT@.
    EventType -> Maybe Text
code :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services service that is affected by the event. For
    -- example, @EC2@, @RDS@.
    EventType -> Maybe Text
service :: Prelude.Maybe Prelude.Text
  }
  deriving (EventType -> EventType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EventType -> EventType -> Bool
$c/= :: EventType -> EventType -> Bool
== :: EventType -> EventType -> Bool
$c== :: EventType -> EventType -> Bool
Prelude.Eq, ReadPrec [EventType]
ReadPrec EventType
Int -> ReadS EventType
ReadS [EventType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EventType]
$creadListPrec :: ReadPrec [EventType]
readPrec :: ReadPrec EventType
$creadPrec :: ReadPrec EventType
readList :: ReadS [EventType]
$creadList :: ReadS [EventType]
readsPrec :: Int -> ReadS EventType
$creadsPrec :: Int -> ReadS EventType
Prelude.Read, Int -> EventType -> ShowS
[EventType] -> ShowS
EventType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EventType] -> ShowS
$cshowList :: [EventType] -> ShowS
show :: EventType -> String
$cshow :: EventType -> String
showsPrec :: Int -> EventType -> ShowS
$cshowsPrec :: Int -> EventType -> ShowS
Prelude.Show, forall x. Rep EventType x -> EventType
forall x. EventType -> Rep EventType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EventType x -> EventType
$cfrom :: forall x. EventType -> Rep EventType x
Prelude.Generic)

-- |
-- Create a value of 'EventType' 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:
--
-- 'category', 'eventType_category' - A list of event type category codes. Possible values are @issue@,
-- @accountNotification@, or @scheduledChange@. Currently, the
-- @investigation@ value isn\'t supported at this time.
--
-- 'code', 'eventType_code' - The unique identifier for the event type. The format is
-- @AWS_@/@SERVICE@/@_@/@DESCRIPTION@/@ @; for example,
-- @AWS_EC2_SYSTEM_MAINTENANCE_EVENT@.
--
-- 'service', 'eventType_service' - The Amazon Web Services service that is affected by the event. For
-- example, @EC2@, @RDS@.
newEventType ::
  EventType
newEventType :: EventType
newEventType =
  EventType'
    { $sel:category:EventType' :: Maybe EventTypeCategory
category = forall a. Maybe a
Prelude.Nothing,
      $sel:code:EventType' :: Maybe Text
code = forall a. Maybe a
Prelude.Nothing,
      $sel:service:EventType' :: Maybe Text
service = forall a. Maybe a
Prelude.Nothing
    }

-- | A list of event type category codes. Possible values are @issue@,
-- @accountNotification@, or @scheduledChange@. Currently, the
-- @investigation@ value isn\'t supported at this time.
eventType_category :: Lens.Lens' EventType (Prelude.Maybe EventTypeCategory)
eventType_category :: Lens' EventType (Maybe EventTypeCategory)
eventType_category = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EventType' {Maybe EventTypeCategory
category :: Maybe EventTypeCategory
$sel:category:EventType' :: EventType -> Maybe EventTypeCategory
category} -> Maybe EventTypeCategory
category) (\s :: EventType
s@EventType' {} Maybe EventTypeCategory
a -> EventType
s {$sel:category:EventType' :: Maybe EventTypeCategory
category = Maybe EventTypeCategory
a} :: EventType)

-- | The unique identifier for the event type. The format is
-- @AWS_@/@SERVICE@/@_@/@DESCRIPTION@/@ @; for example,
-- @AWS_EC2_SYSTEM_MAINTENANCE_EVENT@.
eventType_code :: Lens.Lens' EventType (Prelude.Maybe Prelude.Text)
eventType_code :: Lens' EventType (Maybe Text)
eventType_code = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EventType' {Maybe Text
code :: Maybe Text
$sel:code:EventType' :: EventType -> Maybe Text
code} -> Maybe Text
code) (\s :: EventType
s@EventType' {} Maybe Text
a -> EventType
s {$sel:code:EventType' :: Maybe Text
code = Maybe Text
a} :: EventType)

-- | The Amazon Web Services service that is affected by the event. For
-- example, @EC2@, @RDS@.
eventType_service :: Lens.Lens' EventType (Prelude.Maybe Prelude.Text)
eventType_service :: Lens' EventType (Maybe Text)
eventType_service = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EventType' {Maybe Text
service :: Maybe Text
$sel:service:EventType' :: EventType -> Maybe Text
service} -> Maybe Text
service) (\s :: EventType
s@EventType' {} Maybe Text
a -> EventType
s {$sel:service:EventType' :: Maybe Text
service = Maybe Text
a} :: EventType)

instance Data.FromJSON EventType where
  parseJSON :: Value -> Parser EventType
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"EventType"
      ( \Object
x ->
          Maybe EventTypeCategory -> Maybe Text -> Maybe Text -> EventType
EventType'
            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
"category")
            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
"code")
            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
"service")
      )

instance Prelude.Hashable EventType where
  hashWithSalt :: Int -> EventType -> Int
hashWithSalt Int
_salt EventType' {Maybe Text
Maybe EventTypeCategory
service :: Maybe Text
code :: Maybe Text
category :: Maybe EventTypeCategory
$sel:service:EventType' :: EventType -> Maybe Text
$sel:code:EventType' :: EventType -> Maybe Text
$sel:category:EventType' :: EventType -> Maybe EventTypeCategory
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EventTypeCategory
category
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
code
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
service

instance Prelude.NFData EventType where
  rnf :: EventType -> ()
rnf EventType' {Maybe Text
Maybe EventTypeCategory
service :: Maybe Text
code :: Maybe Text
category :: Maybe EventTypeCategory
$sel:service:EventType' :: EventType -> Maybe Text
$sel:code:EventType' :: EventType -> Maybe Text
$sel:category:EventType' :: EventType -> Maybe EventTypeCategory
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe EventTypeCategory
category
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
code
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
service