{-# 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.SSM.Types.OpsItem
-- 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.SSM.Types.OpsItem 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.SSM.Types.OpsItemDataValue
import Amazonka.SSM.Types.OpsItemNotification
import Amazonka.SSM.Types.OpsItemStatus
import Amazonka.SSM.Types.RelatedOpsItem

-- | Operations engineers and IT professionals use Amazon Web Services
-- Systems Manager OpsCenter to view, investigate, and remediate
-- operational work items (OpsItems) impacting the performance and health
-- of their Amazon Web Services resources. OpsCenter is integrated with
-- Amazon EventBridge and Amazon CloudWatch. This means you can configure
-- these services to automatically create an OpsItem in OpsCenter when a
-- CloudWatch alarm enters the ALARM state or when EventBridge processes an
-- event from any Amazon Web Services service that publishes events.
-- Configuring Amazon CloudWatch alarms and EventBridge events to
-- automatically create OpsItems allows you to quickly diagnose and
-- remediate issues with Amazon Web Services resources from a single
-- console.
--
-- To help you diagnose issues, each OpsItem includes contextually relevant
-- information such as the name and ID of the Amazon Web Services resource
-- that generated the OpsItem, alarm or event details, alarm history, and
-- an alarm timeline graph. For the Amazon Web Services resource, OpsCenter
-- aggregates information from Config, CloudTrail logs, and EventBridge, so
-- you don\'t have to navigate across multiple console pages during your
-- investigation. For more information, see
-- <https://docs.aws.amazon.com/systems-manager/latest/userguide/OpsCenter.html OpsCenter>
-- in the /Amazon Web Services Systems Manager User Guide/.
--
-- /See:/ 'newOpsItem' smart constructor.
data OpsItem = OpsItem'
  { -- | The time a runbook workflow ended. Currently reported only for the
    -- OpsItem type @\/aws\/changerequest@.
    OpsItem -> Maybe POSIX
actualEndTime :: Prelude.Maybe Data.POSIX,
    -- | The time a runbook workflow started. Currently reported only for the
    -- OpsItem type @\/aws\/changerequest@.
    OpsItem -> Maybe POSIX
actualStartTime :: Prelude.Maybe Data.POSIX,
    -- | An OpsItem category. Category options include: Availability, Cost,
    -- Performance, Recovery, Security.
    OpsItem -> Maybe Text
category :: Prelude.Maybe Prelude.Text,
    -- | The ARN of the Amazon Web Services account that created the OpsItem.
    OpsItem -> Maybe Text
createdBy :: Prelude.Maybe Prelude.Text,
    -- | The date and time the OpsItem was created.
    OpsItem -> Maybe POSIX
createdTime :: Prelude.Maybe Data.POSIX,
    -- | The OpsItem description.
    OpsItem -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The ARN of the Amazon Web Services account that last updated the
    -- OpsItem.
    OpsItem -> Maybe Text
lastModifiedBy :: Prelude.Maybe Prelude.Text,
    -- | The date and time the OpsItem was last updated.
    OpsItem -> Maybe POSIX
lastModifiedTime :: Prelude.Maybe Data.POSIX,
    -- | The Amazon Resource Name (ARN) of an Amazon Simple Notification Service
    -- (Amazon SNS) topic where notifications are sent when this OpsItem is
    -- edited or changed.
    OpsItem -> Maybe [OpsItemNotification]
notifications :: Prelude.Maybe [OpsItemNotification],
    -- | Operational data is custom data that provides useful reference details
    -- about the OpsItem. For example, you can specify log files, error
    -- strings, license keys, troubleshooting tips, or other relevant data. You
    -- enter operational data as key-value pairs. The key has a maximum length
    -- of 128 characters. The value has a maximum size of 20 KB.
    --
    -- Operational data keys /can\'t/ begin with the following: @amazon@,
    -- @aws@, @amzn@, @ssm@, @\/amazon@, @\/aws@, @\/amzn@, @\/ssm@.
    --
    -- You can choose to make the data searchable by other users in the account
    -- or you can restrict search access. Searchable data means that all users
    -- with access to the OpsItem Overview page (as provided by the
    -- DescribeOpsItems API operation) can view and search on the specified
    -- data. Operational data that isn\'t searchable is only viewable by users
    -- who have access to the OpsItem (as provided by the GetOpsItem API
    -- operation).
    --
    -- Use the @\/aws\/resources@ key in OperationalData to specify a related
    -- resource in the request. Use the @\/aws\/automations@ key in
    -- OperationalData to associate an Automation runbook with the OpsItem. To
    -- view Amazon Web Services CLI example commands that use these keys, see
    -- <https://docs.aws.amazon.com/systems-manager/latest/userguide/OpsCenter-creating-OpsItems.html#OpsCenter-manually-create-OpsItems Creating OpsItems manually>
    -- in the /Amazon Web Services Systems Manager User Guide/.
    OpsItem -> Maybe (HashMap Text OpsItemDataValue)
operationalData :: Prelude.Maybe (Prelude.HashMap Prelude.Text OpsItemDataValue),
    -- | The OpsItem Amazon Resource Name (ARN).
    OpsItem -> Maybe Text
opsItemArn :: Prelude.Maybe Prelude.Text,
    -- | The ID of the OpsItem.
    OpsItem -> Maybe Text
opsItemId :: Prelude.Maybe Prelude.Text,
    -- | The type of OpsItem. Systems Manager supports the following types of
    -- OpsItems:
    --
    -- -   @\/aws\/issue@
    --
    --     This type of OpsItem is used for default OpsItems created by
    --     OpsCenter.
    --
    -- -   @\/aws\/changerequest@
    --
    --     This type of OpsItem is used by Change Manager for reviewing and
    --     approving or rejecting change requests.
    --
    -- -   @\/aws\/insights@
    --
    --     This type of OpsItem is used by OpsCenter for aggregating and
    --     reporting on duplicate OpsItems.
    OpsItem -> Maybe Text
opsItemType :: Prelude.Maybe Prelude.Text,
    -- | The time specified in a change request for a runbook workflow to end.
    -- Currently supported only for the OpsItem type @\/aws\/changerequest@.
    OpsItem -> Maybe POSIX
plannedEndTime :: Prelude.Maybe Data.POSIX,
    -- | The time specified in a change request for a runbook workflow to start.
    -- Currently supported only for the OpsItem type @\/aws\/changerequest@.
    OpsItem -> Maybe POSIX
plannedStartTime :: Prelude.Maybe Data.POSIX,
    -- | The importance of this OpsItem in relation to other OpsItems in the
    -- system.
    OpsItem -> Maybe Natural
priority :: Prelude.Maybe Prelude.Natural,
    -- | One or more OpsItems that share something in common with the current
    -- OpsItem. For example, related OpsItems can include OpsItems with similar
    -- error messages, impacted resources, or statuses for the impacted
    -- resource.
    OpsItem -> Maybe [RelatedOpsItem]
relatedOpsItems :: Prelude.Maybe [RelatedOpsItem],
    -- | The severity of the OpsItem. Severity options range from 1 to 4.
    OpsItem -> Maybe Text
severity :: Prelude.Maybe Prelude.Text,
    -- | The origin of the OpsItem, such as Amazon EC2 or Systems Manager. The
    -- impacted resource is a subset of source.
    OpsItem -> Maybe Text
source :: Prelude.Maybe Prelude.Text,
    -- | The OpsItem status. Status can be @Open@, @In Progress@, or @Resolved@.
    -- For more information, see
    -- <https://docs.aws.amazon.com/systems-manager/latest/userguide/OpsCenter-working-with-OpsItems-editing-details.html Editing OpsItem details>
    -- in the /Amazon Web Services Systems Manager User Guide/.
    OpsItem -> Maybe OpsItemStatus
status :: Prelude.Maybe OpsItemStatus,
    -- | A short heading that describes the nature of the OpsItem and the
    -- impacted resource.
    OpsItem -> Maybe Text
title :: Prelude.Maybe Prelude.Text,
    -- | The version of this OpsItem. Each time the OpsItem is edited the version
    -- number increments by one.
    OpsItem -> Maybe Text
version :: Prelude.Maybe Prelude.Text
  }
  deriving (OpsItem -> OpsItem -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OpsItem -> OpsItem -> Bool
$c/= :: OpsItem -> OpsItem -> Bool
== :: OpsItem -> OpsItem -> Bool
$c== :: OpsItem -> OpsItem -> Bool
Prelude.Eq, ReadPrec [OpsItem]
ReadPrec OpsItem
Int -> ReadS OpsItem
ReadS [OpsItem]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [OpsItem]
$creadListPrec :: ReadPrec [OpsItem]
readPrec :: ReadPrec OpsItem
$creadPrec :: ReadPrec OpsItem
readList :: ReadS [OpsItem]
$creadList :: ReadS [OpsItem]
readsPrec :: Int -> ReadS OpsItem
$creadsPrec :: Int -> ReadS OpsItem
Prelude.Read, Int -> OpsItem -> ShowS
[OpsItem] -> ShowS
OpsItem -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OpsItem] -> ShowS
$cshowList :: [OpsItem] -> ShowS
show :: OpsItem -> String
$cshow :: OpsItem -> String
showsPrec :: Int -> OpsItem -> ShowS
$cshowsPrec :: Int -> OpsItem -> ShowS
Prelude.Show, forall x. Rep OpsItem x -> OpsItem
forall x. OpsItem -> Rep OpsItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OpsItem x -> OpsItem
$cfrom :: forall x. OpsItem -> Rep OpsItem x
Prelude.Generic)

-- |
-- Create a value of 'OpsItem' 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:
--
-- 'actualEndTime', 'opsItem_actualEndTime' - The time a runbook workflow ended. Currently reported only for the
-- OpsItem type @\/aws\/changerequest@.
--
-- 'actualStartTime', 'opsItem_actualStartTime' - The time a runbook workflow started. Currently reported only for the
-- OpsItem type @\/aws\/changerequest@.
--
-- 'category', 'opsItem_category' - An OpsItem category. Category options include: Availability, Cost,
-- Performance, Recovery, Security.
--
-- 'createdBy', 'opsItem_createdBy' - The ARN of the Amazon Web Services account that created the OpsItem.
--
-- 'createdTime', 'opsItem_createdTime' - The date and time the OpsItem was created.
--
-- 'description', 'opsItem_description' - The OpsItem description.
--
-- 'lastModifiedBy', 'opsItem_lastModifiedBy' - The ARN of the Amazon Web Services account that last updated the
-- OpsItem.
--
-- 'lastModifiedTime', 'opsItem_lastModifiedTime' - The date and time the OpsItem was last updated.
--
-- 'notifications', 'opsItem_notifications' - The Amazon Resource Name (ARN) of an Amazon Simple Notification Service
-- (Amazon SNS) topic where notifications are sent when this OpsItem is
-- edited or changed.
--
-- 'operationalData', 'opsItem_operationalData' - Operational data is custom data that provides useful reference details
-- about the OpsItem. For example, you can specify log files, error
-- strings, license keys, troubleshooting tips, or other relevant data. You
-- enter operational data as key-value pairs. The key has a maximum length
-- of 128 characters. The value has a maximum size of 20 KB.
--
-- Operational data keys /can\'t/ begin with the following: @amazon@,
-- @aws@, @amzn@, @ssm@, @\/amazon@, @\/aws@, @\/amzn@, @\/ssm@.
--
-- You can choose to make the data searchable by other users in the account
-- or you can restrict search access. Searchable data means that all users
-- with access to the OpsItem Overview page (as provided by the
-- DescribeOpsItems API operation) can view and search on the specified
-- data. Operational data that isn\'t searchable is only viewable by users
-- who have access to the OpsItem (as provided by the GetOpsItem API
-- operation).
--
-- Use the @\/aws\/resources@ key in OperationalData to specify a related
-- resource in the request. Use the @\/aws\/automations@ key in
-- OperationalData to associate an Automation runbook with the OpsItem. To
-- view Amazon Web Services CLI example commands that use these keys, see
-- <https://docs.aws.amazon.com/systems-manager/latest/userguide/OpsCenter-creating-OpsItems.html#OpsCenter-manually-create-OpsItems Creating OpsItems manually>
-- in the /Amazon Web Services Systems Manager User Guide/.
--
-- 'opsItemArn', 'opsItem_opsItemArn' - The OpsItem Amazon Resource Name (ARN).
--
-- 'opsItemId', 'opsItem_opsItemId' - The ID of the OpsItem.
--
-- 'opsItemType', 'opsItem_opsItemType' - The type of OpsItem. Systems Manager supports the following types of
-- OpsItems:
--
-- -   @\/aws\/issue@
--
--     This type of OpsItem is used for default OpsItems created by
--     OpsCenter.
--
-- -   @\/aws\/changerequest@
--
--     This type of OpsItem is used by Change Manager for reviewing and
--     approving or rejecting change requests.
--
-- -   @\/aws\/insights@
--
--     This type of OpsItem is used by OpsCenter for aggregating and
--     reporting on duplicate OpsItems.
--
-- 'plannedEndTime', 'opsItem_plannedEndTime' - The time specified in a change request for a runbook workflow to end.
-- Currently supported only for the OpsItem type @\/aws\/changerequest@.
--
-- 'plannedStartTime', 'opsItem_plannedStartTime' - The time specified in a change request for a runbook workflow to start.
-- Currently supported only for the OpsItem type @\/aws\/changerequest@.
--
-- 'priority', 'opsItem_priority' - The importance of this OpsItem in relation to other OpsItems in the
-- system.
--
-- 'relatedOpsItems', 'opsItem_relatedOpsItems' - One or more OpsItems that share something in common with the current
-- OpsItem. For example, related OpsItems can include OpsItems with similar
-- error messages, impacted resources, or statuses for the impacted
-- resource.
--
-- 'severity', 'opsItem_severity' - The severity of the OpsItem. Severity options range from 1 to 4.
--
-- 'source', 'opsItem_source' - The origin of the OpsItem, such as Amazon EC2 or Systems Manager. The
-- impacted resource is a subset of source.
--
-- 'status', 'opsItem_status' - The OpsItem status. Status can be @Open@, @In Progress@, or @Resolved@.
-- For more information, see
-- <https://docs.aws.amazon.com/systems-manager/latest/userguide/OpsCenter-working-with-OpsItems-editing-details.html Editing OpsItem details>
-- in the /Amazon Web Services Systems Manager User Guide/.
--
-- 'title', 'opsItem_title' - A short heading that describes the nature of the OpsItem and the
-- impacted resource.
--
-- 'version', 'opsItem_version' - The version of this OpsItem. Each time the OpsItem is edited the version
-- number increments by one.
newOpsItem ::
  OpsItem
newOpsItem :: OpsItem
newOpsItem =
  OpsItem'
    { $sel:actualEndTime:OpsItem' :: Maybe POSIX
actualEndTime = forall a. Maybe a
Prelude.Nothing,
      $sel:actualStartTime:OpsItem' :: Maybe POSIX
actualStartTime = forall a. Maybe a
Prelude.Nothing,
      $sel:category:OpsItem' :: Maybe Text
category = forall a. Maybe a
Prelude.Nothing,
      $sel:createdBy:OpsItem' :: Maybe Text
createdBy = forall a. Maybe a
Prelude.Nothing,
      $sel:createdTime:OpsItem' :: Maybe POSIX
createdTime = forall a. Maybe a
Prelude.Nothing,
      $sel:description:OpsItem' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedBy:OpsItem' :: Maybe Text
lastModifiedBy = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedTime:OpsItem' :: Maybe POSIX
lastModifiedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:notifications:OpsItem' :: Maybe [OpsItemNotification]
notifications = forall a. Maybe a
Prelude.Nothing,
      $sel:operationalData:OpsItem' :: Maybe (HashMap Text OpsItemDataValue)
operationalData = forall a. Maybe a
Prelude.Nothing,
      $sel:opsItemArn:OpsItem' :: Maybe Text
opsItemArn = forall a. Maybe a
Prelude.Nothing,
      $sel:opsItemId:OpsItem' :: Maybe Text
opsItemId = forall a. Maybe a
Prelude.Nothing,
      $sel:opsItemType:OpsItem' :: Maybe Text
opsItemType = forall a. Maybe a
Prelude.Nothing,
      $sel:plannedEndTime:OpsItem' :: Maybe POSIX
plannedEndTime = forall a. Maybe a
Prelude.Nothing,
      $sel:plannedStartTime:OpsItem' :: Maybe POSIX
plannedStartTime = forall a. Maybe a
Prelude.Nothing,
      $sel:priority:OpsItem' :: Maybe Natural
priority = forall a. Maybe a
Prelude.Nothing,
      $sel:relatedOpsItems:OpsItem' :: Maybe [RelatedOpsItem]
relatedOpsItems = forall a. Maybe a
Prelude.Nothing,
      $sel:severity:OpsItem' :: Maybe Text
severity = forall a. Maybe a
Prelude.Nothing,
      $sel:source:OpsItem' :: Maybe Text
source = forall a. Maybe a
Prelude.Nothing,
      $sel:status:OpsItem' :: Maybe OpsItemStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:title:OpsItem' :: Maybe Text
title = forall a. Maybe a
Prelude.Nothing,
      $sel:version:OpsItem' :: Maybe Text
version = forall a. Maybe a
Prelude.Nothing
    }

-- | The time a runbook workflow ended. Currently reported only for the
-- OpsItem type @\/aws\/changerequest@.
opsItem_actualEndTime :: Lens.Lens' OpsItem (Prelude.Maybe Prelude.UTCTime)
opsItem_actualEndTime :: Lens' OpsItem (Maybe UTCTime)
opsItem_actualEndTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OpsItem' {Maybe POSIX
actualEndTime :: Maybe POSIX
$sel:actualEndTime:OpsItem' :: OpsItem -> Maybe POSIX
actualEndTime} -> Maybe POSIX
actualEndTime) (\s :: OpsItem
s@OpsItem' {} Maybe POSIX
a -> OpsItem
s {$sel:actualEndTime:OpsItem' :: Maybe POSIX
actualEndTime = Maybe POSIX
a} :: OpsItem) 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

-- | The time a runbook workflow started. Currently reported only for the
-- OpsItem type @\/aws\/changerequest@.
opsItem_actualStartTime :: Lens.Lens' OpsItem (Prelude.Maybe Prelude.UTCTime)
opsItem_actualStartTime :: Lens' OpsItem (Maybe UTCTime)
opsItem_actualStartTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OpsItem' {Maybe POSIX
actualStartTime :: Maybe POSIX
$sel:actualStartTime:OpsItem' :: OpsItem -> Maybe POSIX
actualStartTime} -> Maybe POSIX
actualStartTime) (\s :: OpsItem
s@OpsItem' {} Maybe POSIX
a -> OpsItem
s {$sel:actualStartTime:OpsItem' :: Maybe POSIX
actualStartTime = Maybe POSIX
a} :: OpsItem) 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

-- | An OpsItem category. Category options include: Availability, Cost,
-- Performance, Recovery, Security.
opsItem_category :: Lens.Lens' OpsItem (Prelude.Maybe Prelude.Text)
opsItem_category :: Lens' OpsItem (Maybe Text)
opsItem_category = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OpsItem' {Maybe Text
category :: Maybe Text
$sel:category:OpsItem' :: OpsItem -> Maybe Text
category} -> Maybe Text
category) (\s :: OpsItem
s@OpsItem' {} Maybe Text
a -> OpsItem
s {$sel:category:OpsItem' :: Maybe Text
category = Maybe Text
a} :: OpsItem)

-- | The ARN of the Amazon Web Services account that created the OpsItem.
opsItem_createdBy :: Lens.Lens' OpsItem (Prelude.Maybe Prelude.Text)
opsItem_createdBy :: Lens' OpsItem (Maybe Text)
opsItem_createdBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OpsItem' {Maybe Text
createdBy :: Maybe Text
$sel:createdBy:OpsItem' :: OpsItem -> Maybe Text
createdBy} -> Maybe Text
createdBy) (\s :: OpsItem
s@OpsItem' {} Maybe Text
a -> OpsItem
s {$sel:createdBy:OpsItem' :: Maybe Text
createdBy = Maybe Text
a} :: OpsItem)

-- | The date and time the OpsItem was created.
opsItem_createdTime :: Lens.Lens' OpsItem (Prelude.Maybe Prelude.UTCTime)
opsItem_createdTime :: Lens' OpsItem (Maybe UTCTime)
opsItem_createdTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OpsItem' {Maybe POSIX
createdTime :: Maybe POSIX
$sel:createdTime:OpsItem' :: OpsItem -> Maybe POSIX
createdTime} -> Maybe POSIX
createdTime) (\s :: OpsItem
s@OpsItem' {} Maybe POSIX
a -> OpsItem
s {$sel:createdTime:OpsItem' :: Maybe POSIX
createdTime = Maybe POSIX
a} :: OpsItem) 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

-- | The OpsItem description.
opsItem_description :: Lens.Lens' OpsItem (Prelude.Maybe Prelude.Text)
opsItem_description :: Lens' OpsItem (Maybe Text)
opsItem_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OpsItem' {Maybe Text
description :: Maybe Text
$sel:description:OpsItem' :: OpsItem -> Maybe Text
description} -> Maybe Text
description) (\s :: OpsItem
s@OpsItem' {} Maybe Text
a -> OpsItem
s {$sel:description:OpsItem' :: Maybe Text
description = Maybe Text
a} :: OpsItem)

-- | The ARN of the Amazon Web Services account that last updated the
-- OpsItem.
opsItem_lastModifiedBy :: Lens.Lens' OpsItem (Prelude.Maybe Prelude.Text)
opsItem_lastModifiedBy :: Lens' OpsItem (Maybe Text)
opsItem_lastModifiedBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OpsItem' {Maybe Text
lastModifiedBy :: Maybe Text
$sel:lastModifiedBy:OpsItem' :: OpsItem -> Maybe Text
lastModifiedBy} -> Maybe Text
lastModifiedBy) (\s :: OpsItem
s@OpsItem' {} Maybe Text
a -> OpsItem
s {$sel:lastModifiedBy:OpsItem' :: Maybe Text
lastModifiedBy = Maybe Text
a} :: OpsItem)

-- | The date and time the OpsItem was last updated.
opsItem_lastModifiedTime :: Lens.Lens' OpsItem (Prelude.Maybe Prelude.UTCTime)
opsItem_lastModifiedTime :: Lens' OpsItem (Maybe UTCTime)
opsItem_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OpsItem' {Maybe POSIX
lastModifiedTime :: Maybe POSIX
$sel:lastModifiedTime:OpsItem' :: OpsItem -> Maybe POSIX
lastModifiedTime} -> Maybe POSIX
lastModifiedTime) (\s :: OpsItem
s@OpsItem' {} Maybe POSIX
a -> OpsItem
s {$sel:lastModifiedTime:OpsItem' :: Maybe POSIX
lastModifiedTime = Maybe POSIX
a} :: OpsItem) 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

-- | The Amazon Resource Name (ARN) of an Amazon Simple Notification Service
-- (Amazon SNS) topic where notifications are sent when this OpsItem is
-- edited or changed.
opsItem_notifications :: Lens.Lens' OpsItem (Prelude.Maybe [OpsItemNotification])
opsItem_notifications :: Lens' OpsItem (Maybe [OpsItemNotification])
opsItem_notifications = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OpsItem' {Maybe [OpsItemNotification]
notifications :: Maybe [OpsItemNotification]
$sel:notifications:OpsItem' :: OpsItem -> Maybe [OpsItemNotification]
notifications} -> Maybe [OpsItemNotification]
notifications) (\s :: OpsItem
s@OpsItem' {} Maybe [OpsItemNotification]
a -> OpsItem
s {$sel:notifications:OpsItem' :: Maybe [OpsItemNotification]
notifications = Maybe [OpsItemNotification]
a} :: OpsItem) 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

-- | Operational data is custom data that provides useful reference details
-- about the OpsItem. For example, you can specify log files, error
-- strings, license keys, troubleshooting tips, or other relevant data. You
-- enter operational data as key-value pairs. The key has a maximum length
-- of 128 characters. The value has a maximum size of 20 KB.
--
-- Operational data keys /can\'t/ begin with the following: @amazon@,
-- @aws@, @amzn@, @ssm@, @\/amazon@, @\/aws@, @\/amzn@, @\/ssm@.
--
-- You can choose to make the data searchable by other users in the account
-- or you can restrict search access. Searchable data means that all users
-- with access to the OpsItem Overview page (as provided by the
-- DescribeOpsItems API operation) can view and search on the specified
-- data. Operational data that isn\'t searchable is only viewable by users
-- who have access to the OpsItem (as provided by the GetOpsItem API
-- operation).
--
-- Use the @\/aws\/resources@ key in OperationalData to specify a related
-- resource in the request. Use the @\/aws\/automations@ key in
-- OperationalData to associate an Automation runbook with the OpsItem. To
-- view Amazon Web Services CLI example commands that use these keys, see
-- <https://docs.aws.amazon.com/systems-manager/latest/userguide/OpsCenter-creating-OpsItems.html#OpsCenter-manually-create-OpsItems Creating OpsItems manually>
-- in the /Amazon Web Services Systems Manager User Guide/.
opsItem_operationalData :: Lens.Lens' OpsItem (Prelude.Maybe (Prelude.HashMap Prelude.Text OpsItemDataValue))
opsItem_operationalData :: Lens' OpsItem (Maybe (HashMap Text OpsItemDataValue))
opsItem_operationalData = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OpsItem' {Maybe (HashMap Text OpsItemDataValue)
operationalData :: Maybe (HashMap Text OpsItemDataValue)
$sel:operationalData:OpsItem' :: OpsItem -> Maybe (HashMap Text OpsItemDataValue)
operationalData} -> Maybe (HashMap Text OpsItemDataValue)
operationalData) (\s :: OpsItem
s@OpsItem' {} Maybe (HashMap Text OpsItemDataValue)
a -> OpsItem
s {$sel:operationalData:OpsItem' :: Maybe (HashMap Text OpsItemDataValue)
operationalData = Maybe (HashMap Text OpsItemDataValue)
a} :: OpsItem) 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 OpsItem Amazon Resource Name (ARN).
opsItem_opsItemArn :: Lens.Lens' OpsItem (Prelude.Maybe Prelude.Text)
opsItem_opsItemArn :: Lens' OpsItem (Maybe Text)
opsItem_opsItemArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OpsItem' {Maybe Text
opsItemArn :: Maybe Text
$sel:opsItemArn:OpsItem' :: OpsItem -> Maybe Text
opsItemArn} -> Maybe Text
opsItemArn) (\s :: OpsItem
s@OpsItem' {} Maybe Text
a -> OpsItem
s {$sel:opsItemArn:OpsItem' :: Maybe Text
opsItemArn = Maybe Text
a} :: OpsItem)

-- | The ID of the OpsItem.
opsItem_opsItemId :: Lens.Lens' OpsItem (Prelude.Maybe Prelude.Text)
opsItem_opsItemId :: Lens' OpsItem (Maybe Text)
opsItem_opsItemId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OpsItem' {Maybe Text
opsItemId :: Maybe Text
$sel:opsItemId:OpsItem' :: OpsItem -> Maybe Text
opsItemId} -> Maybe Text
opsItemId) (\s :: OpsItem
s@OpsItem' {} Maybe Text
a -> OpsItem
s {$sel:opsItemId:OpsItem' :: Maybe Text
opsItemId = Maybe Text
a} :: OpsItem)

-- | The type of OpsItem. Systems Manager supports the following types of
-- OpsItems:
--
-- -   @\/aws\/issue@
--
--     This type of OpsItem is used for default OpsItems created by
--     OpsCenter.
--
-- -   @\/aws\/changerequest@
--
--     This type of OpsItem is used by Change Manager for reviewing and
--     approving or rejecting change requests.
--
-- -   @\/aws\/insights@
--
--     This type of OpsItem is used by OpsCenter for aggregating and
--     reporting on duplicate OpsItems.
opsItem_opsItemType :: Lens.Lens' OpsItem (Prelude.Maybe Prelude.Text)
opsItem_opsItemType :: Lens' OpsItem (Maybe Text)
opsItem_opsItemType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OpsItem' {Maybe Text
opsItemType :: Maybe Text
$sel:opsItemType:OpsItem' :: OpsItem -> Maybe Text
opsItemType} -> Maybe Text
opsItemType) (\s :: OpsItem
s@OpsItem' {} Maybe Text
a -> OpsItem
s {$sel:opsItemType:OpsItem' :: Maybe Text
opsItemType = Maybe Text
a} :: OpsItem)

-- | The time specified in a change request for a runbook workflow to end.
-- Currently supported only for the OpsItem type @\/aws\/changerequest@.
opsItem_plannedEndTime :: Lens.Lens' OpsItem (Prelude.Maybe Prelude.UTCTime)
opsItem_plannedEndTime :: Lens' OpsItem (Maybe UTCTime)
opsItem_plannedEndTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OpsItem' {Maybe POSIX
plannedEndTime :: Maybe POSIX
$sel:plannedEndTime:OpsItem' :: OpsItem -> Maybe POSIX
plannedEndTime} -> Maybe POSIX
plannedEndTime) (\s :: OpsItem
s@OpsItem' {} Maybe POSIX
a -> OpsItem
s {$sel:plannedEndTime:OpsItem' :: Maybe POSIX
plannedEndTime = Maybe POSIX
a} :: OpsItem) 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

-- | The time specified in a change request for a runbook workflow to start.
-- Currently supported only for the OpsItem type @\/aws\/changerequest@.
opsItem_plannedStartTime :: Lens.Lens' OpsItem (Prelude.Maybe Prelude.UTCTime)
opsItem_plannedStartTime :: Lens' OpsItem (Maybe UTCTime)
opsItem_plannedStartTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OpsItem' {Maybe POSIX
plannedStartTime :: Maybe POSIX
$sel:plannedStartTime:OpsItem' :: OpsItem -> Maybe POSIX
plannedStartTime} -> Maybe POSIX
plannedStartTime) (\s :: OpsItem
s@OpsItem' {} Maybe POSIX
a -> OpsItem
s {$sel:plannedStartTime:OpsItem' :: Maybe POSIX
plannedStartTime = Maybe POSIX
a} :: OpsItem) 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

-- | The importance of this OpsItem in relation to other OpsItems in the
-- system.
opsItem_priority :: Lens.Lens' OpsItem (Prelude.Maybe Prelude.Natural)
opsItem_priority :: Lens' OpsItem (Maybe Natural)
opsItem_priority = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OpsItem' {Maybe Natural
priority :: Maybe Natural
$sel:priority:OpsItem' :: OpsItem -> Maybe Natural
priority} -> Maybe Natural
priority) (\s :: OpsItem
s@OpsItem' {} Maybe Natural
a -> OpsItem
s {$sel:priority:OpsItem' :: Maybe Natural
priority = Maybe Natural
a} :: OpsItem)

-- | One or more OpsItems that share something in common with the current
-- OpsItem. For example, related OpsItems can include OpsItems with similar
-- error messages, impacted resources, or statuses for the impacted
-- resource.
opsItem_relatedOpsItems :: Lens.Lens' OpsItem (Prelude.Maybe [RelatedOpsItem])
opsItem_relatedOpsItems :: Lens' OpsItem (Maybe [RelatedOpsItem])
opsItem_relatedOpsItems = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OpsItem' {Maybe [RelatedOpsItem]
relatedOpsItems :: Maybe [RelatedOpsItem]
$sel:relatedOpsItems:OpsItem' :: OpsItem -> Maybe [RelatedOpsItem]
relatedOpsItems} -> Maybe [RelatedOpsItem]
relatedOpsItems) (\s :: OpsItem
s@OpsItem' {} Maybe [RelatedOpsItem]
a -> OpsItem
s {$sel:relatedOpsItems:OpsItem' :: Maybe [RelatedOpsItem]
relatedOpsItems = Maybe [RelatedOpsItem]
a} :: OpsItem) 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 severity of the OpsItem. Severity options range from 1 to 4.
opsItem_severity :: Lens.Lens' OpsItem (Prelude.Maybe Prelude.Text)
opsItem_severity :: Lens' OpsItem (Maybe Text)
opsItem_severity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OpsItem' {Maybe Text
severity :: Maybe Text
$sel:severity:OpsItem' :: OpsItem -> Maybe Text
severity} -> Maybe Text
severity) (\s :: OpsItem
s@OpsItem' {} Maybe Text
a -> OpsItem
s {$sel:severity:OpsItem' :: Maybe Text
severity = Maybe Text
a} :: OpsItem)

-- | The origin of the OpsItem, such as Amazon EC2 or Systems Manager. The
-- impacted resource is a subset of source.
opsItem_source :: Lens.Lens' OpsItem (Prelude.Maybe Prelude.Text)
opsItem_source :: Lens' OpsItem (Maybe Text)
opsItem_source = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OpsItem' {Maybe Text
source :: Maybe Text
$sel:source:OpsItem' :: OpsItem -> Maybe Text
source} -> Maybe Text
source) (\s :: OpsItem
s@OpsItem' {} Maybe Text
a -> OpsItem
s {$sel:source:OpsItem' :: Maybe Text
source = Maybe Text
a} :: OpsItem)

-- | The OpsItem status. Status can be @Open@, @In Progress@, or @Resolved@.
-- For more information, see
-- <https://docs.aws.amazon.com/systems-manager/latest/userguide/OpsCenter-working-with-OpsItems-editing-details.html Editing OpsItem details>
-- in the /Amazon Web Services Systems Manager User Guide/.
opsItem_status :: Lens.Lens' OpsItem (Prelude.Maybe OpsItemStatus)
opsItem_status :: Lens' OpsItem (Maybe OpsItemStatus)
opsItem_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OpsItem' {Maybe OpsItemStatus
status :: Maybe OpsItemStatus
$sel:status:OpsItem' :: OpsItem -> Maybe OpsItemStatus
status} -> Maybe OpsItemStatus
status) (\s :: OpsItem
s@OpsItem' {} Maybe OpsItemStatus
a -> OpsItem
s {$sel:status:OpsItem' :: Maybe OpsItemStatus
status = Maybe OpsItemStatus
a} :: OpsItem)

-- | A short heading that describes the nature of the OpsItem and the
-- impacted resource.
opsItem_title :: Lens.Lens' OpsItem (Prelude.Maybe Prelude.Text)
opsItem_title :: Lens' OpsItem (Maybe Text)
opsItem_title = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OpsItem' {Maybe Text
title :: Maybe Text
$sel:title:OpsItem' :: OpsItem -> Maybe Text
title} -> Maybe Text
title) (\s :: OpsItem
s@OpsItem' {} Maybe Text
a -> OpsItem
s {$sel:title:OpsItem' :: Maybe Text
title = Maybe Text
a} :: OpsItem)

-- | The version of this OpsItem. Each time the OpsItem is edited the version
-- number increments by one.
opsItem_version :: Lens.Lens' OpsItem (Prelude.Maybe Prelude.Text)
opsItem_version :: Lens' OpsItem (Maybe Text)
opsItem_version = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OpsItem' {Maybe Text
version :: Maybe Text
$sel:version:OpsItem' :: OpsItem -> Maybe Text
version} -> Maybe Text
version) (\s :: OpsItem
s@OpsItem' {} Maybe Text
a -> OpsItem
s {$sel:version:OpsItem' :: Maybe Text
version = Maybe Text
a} :: OpsItem)

instance Data.FromJSON OpsItem where
  parseJSON :: Value -> Parser OpsItem
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"OpsItem"
      ( \Object
x ->
          Maybe POSIX
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe POSIX
-> Maybe [OpsItemNotification]
-> Maybe (HashMap Text OpsItemDataValue)
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe POSIX
-> Maybe POSIX
-> Maybe Natural
-> Maybe [RelatedOpsItem]
-> Maybe Text
-> Maybe Text
-> Maybe OpsItemStatus
-> Maybe Text
-> Maybe Text
-> OpsItem
OpsItem'
            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
"ActualEndTime")
            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
"ActualStartTime")
            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
"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
"CreatedBy")
            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
"CreatedTime")
            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
"Description")
            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
"LastModifiedBy")
            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
"LastModifiedTime")
            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
"Notifications" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            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
"OperationalData"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            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
"OpsItemArn")
            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
"OpsItemId")
            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
"OpsItemType")
            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
"PlannedEndTime")
            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
"PlannedStartTime")
            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
"Priority")
            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
"RelatedOpsItems"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            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
"Severity")
            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
"Source")
            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
"Title")
            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
"Version")
      )

instance Prelude.Hashable OpsItem where
  hashWithSalt :: Int -> OpsItem -> Int
hashWithSalt Int
_salt OpsItem' {Maybe Natural
Maybe [OpsItemNotification]
Maybe [RelatedOpsItem]
Maybe Text
Maybe (HashMap Text OpsItemDataValue)
Maybe POSIX
Maybe OpsItemStatus
version :: Maybe Text
title :: Maybe Text
status :: Maybe OpsItemStatus
source :: Maybe Text
severity :: Maybe Text
relatedOpsItems :: Maybe [RelatedOpsItem]
priority :: Maybe Natural
plannedStartTime :: Maybe POSIX
plannedEndTime :: Maybe POSIX
opsItemType :: Maybe Text
opsItemId :: Maybe Text
opsItemArn :: Maybe Text
operationalData :: Maybe (HashMap Text OpsItemDataValue)
notifications :: Maybe [OpsItemNotification]
lastModifiedTime :: Maybe POSIX
lastModifiedBy :: Maybe Text
description :: Maybe Text
createdTime :: Maybe POSIX
createdBy :: Maybe Text
category :: Maybe Text
actualStartTime :: Maybe POSIX
actualEndTime :: Maybe POSIX
$sel:version:OpsItem' :: OpsItem -> Maybe Text
$sel:title:OpsItem' :: OpsItem -> Maybe Text
$sel:status:OpsItem' :: OpsItem -> Maybe OpsItemStatus
$sel:source:OpsItem' :: OpsItem -> Maybe Text
$sel:severity:OpsItem' :: OpsItem -> Maybe Text
$sel:relatedOpsItems:OpsItem' :: OpsItem -> Maybe [RelatedOpsItem]
$sel:priority:OpsItem' :: OpsItem -> Maybe Natural
$sel:plannedStartTime:OpsItem' :: OpsItem -> Maybe POSIX
$sel:plannedEndTime:OpsItem' :: OpsItem -> Maybe POSIX
$sel:opsItemType:OpsItem' :: OpsItem -> Maybe Text
$sel:opsItemId:OpsItem' :: OpsItem -> Maybe Text
$sel:opsItemArn:OpsItem' :: OpsItem -> Maybe Text
$sel:operationalData:OpsItem' :: OpsItem -> Maybe (HashMap Text OpsItemDataValue)
$sel:notifications:OpsItem' :: OpsItem -> Maybe [OpsItemNotification]
$sel:lastModifiedTime:OpsItem' :: OpsItem -> Maybe POSIX
$sel:lastModifiedBy:OpsItem' :: OpsItem -> Maybe Text
$sel:description:OpsItem' :: OpsItem -> Maybe Text
$sel:createdTime:OpsItem' :: OpsItem -> Maybe POSIX
$sel:createdBy:OpsItem' :: OpsItem -> Maybe Text
$sel:category:OpsItem' :: OpsItem -> Maybe Text
$sel:actualStartTime:OpsItem' :: OpsItem -> Maybe POSIX
$sel:actualEndTime:OpsItem' :: OpsItem -> Maybe POSIX
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
actualEndTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
actualStartTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
category
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
createdBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createdTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
lastModifiedBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
lastModifiedTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [OpsItemNotification]
notifications
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text OpsItemDataValue)
operationalData
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
opsItemArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
opsItemId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
opsItemType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
plannedEndTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
plannedStartTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
priority
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [RelatedOpsItem]
relatedOpsItems
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
severity
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
source
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe OpsItemStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
title
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
version

instance Prelude.NFData OpsItem where
  rnf :: OpsItem -> ()
rnf OpsItem' {Maybe Natural
Maybe [OpsItemNotification]
Maybe [RelatedOpsItem]
Maybe Text
Maybe (HashMap Text OpsItemDataValue)
Maybe POSIX
Maybe OpsItemStatus
version :: Maybe Text
title :: Maybe Text
status :: Maybe OpsItemStatus
source :: Maybe Text
severity :: Maybe Text
relatedOpsItems :: Maybe [RelatedOpsItem]
priority :: Maybe Natural
plannedStartTime :: Maybe POSIX
plannedEndTime :: Maybe POSIX
opsItemType :: Maybe Text
opsItemId :: Maybe Text
opsItemArn :: Maybe Text
operationalData :: Maybe (HashMap Text OpsItemDataValue)
notifications :: Maybe [OpsItemNotification]
lastModifiedTime :: Maybe POSIX
lastModifiedBy :: Maybe Text
description :: Maybe Text
createdTime :: Maybe POSIX
createdBy :: Maybe Text
category :: Maybe Text
actualStartTime :: Maybe POSIX
actualEndTime :: Maybe POSIX
$sel:version:OpsItem' :: OpsItem -> Maybe Text
$sel:title:OpsItem' :: OpsItem -> Maybe Text
$sel:status:OpsItem' :: OpsItem -> Maybe OpsItemStatus
$sel:source:OpsItem' :: OpsItem -> Maybe Text
$sel:severity:OpsItem' :: OpsItem -> Maybe Text
$sel:relatedOpsItems:OpsItem' :: OpsItem -> Maybe [RelatedOpsItem]
$sel:priority:OpsItem' :: OpsItem -> Maybe Natural
$sel:plannedStartTime:OpsItem' :: OpsItem -> Maybe POSIX
$sel:plannedEndTime:OpsItem' :: OpsItem -> Maybe POSIX
$sel:opsItemType:OpsItem' :: OpsItem -> Maybe Text
$sel:opsItemId:OpsItem' :: OpsItem -> Maybe Text
$sel:opsItemArn:OpsItem' :: OpsItem -> Maybe Text
$sel:operationalData:OpsItem' :: OpsItem -> Maybe (HashMap Text OpsItemDataValue)
$sel:notifications:OpsItem' :: OpsItem -> Maybe [OpsItemNotification]
$sel:lastModifiedTime:OpsItem' :: OpsItem -> Maybe POSIX
$sel:lastModifiedBy:OpsItem' :: OpsItem -> Maybe Text
$sel:description:OpsItem' :: OpsItem -> Maybe Text
$sel:createdTime:OpsItem' :: OpsItem -> Maybe POSIX
$sel:createdBy:OpsItem' :: OpsItem -> Maybe Text
$sel:category:OpsItem' :: OpsItem -> Maybe Text
$sel:actualStartTime:OpsItem' :: OpsItem -> Maybe POSIX
$sel:actualEndTime:OpsItem' :: OpsItem -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
actualEndTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
actualStartTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
category
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
createdBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
lastModifiedBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastModifiedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [OpsItemNotification]
notifications
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text OpsItemDataValue)
operationalData
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
opsItemArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
opsItemId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
opsItemType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
plannedEndTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
plannedStartTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
priority
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [RelatedOpsItem]
relatedOpsItems
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
severity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
source
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OpsItemStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
title
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
version