{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# 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.UpdateOpsItem
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Edit or change an OpsItem. You must have permission in Identity and
-- Access Management (IAM) to update an OpsItem. For more information, see
-- <https://docs.aws.amazon.com/systems-manager/latest/userguide/OpsCenter-getting-started.html Getting started with OpsCenter>
-- in the /Amazon Web Services Systems Manager User Guide/.
--
-- Operations engineers and IT professionals use Amazon Web Services
-- Systems Manager OpsCenter to view, investigate, and remediate
-- operational issues impacting the performance and health of their Amazon
-- Web Services resources. 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/.
module Amazonka.SSM.UpdateOpsItem
  ( -- * Creating a Request
    UpdateOpsItem (..),
    newUpdateOpsItem,

    -- * Request Lenses
    updateOpsItem_actualEndTime,
    updateOpsItem_actualStartTime,
    updateOpsItem_category,
    updateOpsItem_description,
    updateOpsItem_notifications,
    updateOpsItem_operationalData,
    updateOpsItem_operationalDataToDelete,
    updateOpsItem_opsItemArn,
    updateOpsItem_plannedEndTime,
    updateOpsItem_plannedStartTime,
    updateOpsItem_priority,
    updateOpsItem_relatedOpsItems,
    updateOpsItem_severity,
    updateOpsItem_status,
    updateOpsItem_title,
    updateOpsItem_opsItemId,

    -- * Destructuring the Response
    UpdateOpsItemResponse (..),
    newUpdateOpsItemResponse,

    -- * Response Lenses
    updateOpsItemResponse_httpStatus,
  )
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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.SSM.Types

-- | /See:/ 'newUpdateOpsItem' smart constructor.
data UpdateOpsItem = UpdateOpsItem'
  { -- | The time a runbook workflow ended. Currently reported only for the
    -- OpsItem type @\/aws\/changerequest@.
    UpdateOpsItem -> Maybe POSIX
actualEndTime :: Prelude.Maybe Data.POSIX,
    -- | The time a runbook workflow started. Currently reported only for the
    -- OpsItem type @\/aws\/changerequest@.
    UpdateOpsItem -> Maybe POSIX
actualStartTime :: Prelude.Maybe Data.POSIX,
    -- | Specify a new category for an OpsItem.
    UpdateOpsItem -> Maybe Text
category :: Prelude.Maybe Prelude.Text,
    -- | Update the information about the OpsItem. Provide enough information so
    -- that users reading this OpsItem for the first time understand the issue.
    UpdateOpsItem -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of an SNS topic where notifications are
    -- sent when this OpsItem is edited or changed.
    UpdateOpsItem -> Maybe [OpsItemNotification]
notifications :: Prelude.Maybe [OpsItemNotification],
    -- | Add new keys or edit existing key-value pairs of the OperationalData map
    -- in the OpsItem object.
    --
    -- 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/.
    UpdateOpsItem -> Maybe (HashMap Text OpsItemDataValue)
operationalData :: Prelude.Maybe (Prelude.HashMap Prelude.Text OpsItemDataValue),
    -- | Keys that you want to remove from the OperationalData map.
    UpdateOpsItem -> Maybe [Text]
operationalDataToDelete :: Prelude.Maybe [Prelude.Text],
    -- | The OpsItem Amazon Resource Name (ARN).
    UpdateOpsItem -> Maybe Text
opsItemArn :: 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@.
    UpdateOpsItem -> 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@.
    UpdateOpsItem -> Maybe POSIX
plannedStartTime :: Prelude.Maybe Data.POSIX,
    -- | The importance of this OpsItem in relation to other OpsItems in the
    -- system.
    UpdateOpsItem -> Maybe Natural
priority :: Prelude.Maybe Prelude.Natural,
    -- | One or more OpsItems that share something in common with the current
    -- OpsItems. For example, related OpsItems can include OpsItems with
    -- similar error messages, impacted resources, or statuses for the impacted
    -- resource.
    UpdateOpsItem -> Maybe [RelatedOpsItem]
relatedOpsItems :: Prelude.Maybe [RelatedOpsItem],
    -- | Specify a new severity for an OpsItem.
    UpdateOpsItem -> Maybe Text
severity :: 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.html#OpsCenter-working-with-OpsItems-editing-details Editing OpsItem details>
    -- in the /Amazon Web Services Systems Manager User Guide/.
    UpdateOpsItem -> Maybe OpsItemStatus
status :: Prelude.Maybe OpsItemStatus,
    -- | A short heading that describes the nature of the OpsItem and the
    -- impacted resource.
    UpdateOpsItem -> Maybe Text
title :: Prelude.Maybe Prelude.Text,
    -- | The ID of the OpsItem.
    UpdateOpsItem -> Text
opsItemId :: Prelude.Text
  }
  deriving (UpdateOpsItem -> UpdateOpsItem -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateOpsItem -> UpdateOpsItem -> Bool
$c/= :: UpdateOpsItem -> UpdateOpsItem -> Bool
== :: UpdateOpsItem -> UpdateOpsItem -> Bool
$c== :: UpdateOpsItem -> UpdateOpsItem -> Bool
Prelude.Eq, ReadPrec [UpdateOpsItem]
ReadPrec UpdateOpsItem
Int -> ReadS UpdateOpsItem
ReadS [UpdateOpsItem]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateOpsItem]
$creadListPrec :: ReadPrec [UpdateOpsItem]
readPrec :: ReadPrec UpdateOpsItem
$creadPrec :: ReadPrec UpdateOpsItem
readList :: ReadS [UpdateOpsItem]
$creadList :: ReadS [UpdateOpsItem]
readsPrec :: Int -> ReadS UpdateOpsItem
$creadsPrec :: Int -> ReadS UpdateOpsItem
Prelude.Read, Int -> UpdateOpsItem -> ShowS
[UpdateOpsItem] -> ShowS
UpdateOpsItem -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateOpsItem] -> ShowS
$cshowList :: [UpdateOpsItem] -> ShowS
show :: UpdateOpsItem -> String
$cshow :: UpdateOpsItem -> String
showsPrec :: Int -> UpdateOpsItem -> ShowS
$cshowsPrec :: Int -> UpdateOpsItem -> ShowS
Prelude.Show, forall x. Rep UpdateOpsItem x -> UpdateOpsItem
forall x. UpdateOpsItem -> Rep UpdateOpsItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateOpsItem x -> UpdateOpsItem
$cfrom :: forall x. UpdateOpsItem -> Rep UpdateOpsItem x
Prelude.Generic)

-- |
-- Create a value of 'UpdateOpsItem' 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', 'updateOpsItem_actualEndTime' - The time a runbook workflow ended. Currently reported only for the
-- OpsItem type @\/aws\/changerequest@.
--
-- 'actualStartTime', 'updateOpsItem_actualStartTime' - The time a runbook workflow started. Currently reported only for the
-- OpsItem type @\/aws\/changerequest@.
--
-- 'category', 'updateOpsItem_category' - Specify a new category for an OpsItem.
--
-- 'description', 'updateOpsItem_description' - Update the information about the OpsItem. Provide enough information so
-- that users reading this OpsItem for the first time understand the issue.
--
-- 'notifications', 'updateOpsItem_notifications' - The Amazon Resource Name (ARN) of an SNS topic where notifications are
-- sent when this OpsItem is edited or changed.
--
-- 'operationalData', 'updateOpsItem_operationalData' - Add new keys or edit existing key-value pairs of the OperationalData map
-- in the OpsItem object.
--
-- 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/.
--
-- 'operationalDataToDelete', 'updateOpsItem_operationalDataToDelete' - Keys that you want to remove from the OperationalData map.
--
-- 'opsItemArn', 'updateOpsItem_opsItemArn' - The OpsItem Amazon Resource Name (ARN).
--
-- 'plannedEndTime', 'updateOpsItem_plannedEndTime' - The time specified in a change request for a runbook workflow to end.
-- Currently supported only for the OpsItem type @\/aws\/changerequest@.
--
-- 'plannedStartTime', 'updateOpsItem_plannedStartTime' - The time specified in a change request for a runbook workflow to start.
-- Currently supported only for the OpsItem type @\/aws\/changerequest@.
--
-- 'priority', 'updateOpsItem_priority' - The importance of this OpsItem in relation to other OpsItems in the
-- system.
--
-- 'relatedOpsItems', 'updateOpsItem_relatedOpsItems' - One or more OpsItems that share something in common with the current
-- OpsItems. For example, related OpsItems can include OpsItems with
-- similar error messages, impacted resources, or statuses for the impacted
-- resource.
--
-- 'severity', 'updateOpsItem_severity' - Specify a new severity for an OpsItem.
--
-- 'status', 'updateOpsItem_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.html#OpsCenter-working-with-OpsItems-editing-details Editing OpsItem details>
-- in the /Amazon Web Services Systems Manager User Guide/.
--
-- 'title', 'updateOpsItem_title' - A short heading that describes the nature of the OpsItem and the
-- impacted resource.
--
-- 'opsItemId', 'updateOpsItem_opsItemId' - The ID of the OpsItem.
newUpdateOpsItem ::
  -- | 'opsItemId'
  Prelude.Text ->
  UpdateOpsItem
newUpdateOpsItem :: Text -> UpdateOpsItem
newUpdateOpsItem Text
pOpsItemId_ =
  UpdateOpsItem'
    { $sel:actualEndTime:UpdateOpsItem' :: Maybe POSIX
actualEndTime = forall a. Maybe a
Prelude.Nothing,
      $sel:actualStartTime:UpdateOpsItem' :: Maybe POSIX
actualStartTime = forall a. Maybe a
Prelude.Nothing,
      $sel:category:UpdateOpsItem' :: Maybe Text
category = forall a. Maybe a
Prelude.Nothing,
      $sel:description:UpdateOpsItem' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:notifications:UpdateOpsItem' :: Maybe [OpsItemNotification]
notifications = forall a. Maybe a
Prelude.Nothing,
      $sel:operationalData:UpdateOpsItem' :: Maybe (HashMap Text OpsItemDataValue)
operationalData = forall a. Maybe a
Prelude.Nothing,
      $sel:operationalDataToDelete:UpdateOpsItem' :: Maybe [Text]
operationalDataToDelete = forall a. Maybe a
Prelude.Nothing,
      $sel:opsItemArn:UpdateOpsItem' :: Maybe Text
opsItemArn = forall a. Maybe a
Prelude.Nothing,
      $sel:plannedEndTime:UpdateOpsItem' :: Maybe POSIX
plannedEndTime = forall a. Maybe a
Prelude.Nothing,
      $sel:plannedStartTime:UpdateOpsItem' :: Maybe POSIX
plannedStartTime = forall a. Maybe a
Prelude.Nothing,
      $sel:priority:UpdateOpsItem' :: Maybe Natural
priority = forall a. Maybe a
Prelude.Nothing,
      $sel:relatedOpsItems:UpdateOpsItem' :: Maybe [RelatedOpsItem]
relatedOpsItems = forall a. Maybe a
Prelude.Nothing,
      $sel:severity:UpdateOpsItem' :: Maybe Text
severity = forall a. Maybe a
Prelude.Nothing,
      $sel:status:UpdateOpsItem' :: Maybe OpsItemStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:title:UpdateOpsItem' :: Maybe Text
title = forall a. Maybe a
Prelude.Nothing,
      $sel:opsItemId:UpdateOpsItem' :: Text
opsItemId = Text
pOpsItemId_
    }

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

-- | Specify a new category for an OpsItem.
updateOpsItem_category :: Lens.Lens' UpdateOpsItem (Prelude.Maybe Prelude.Text)
updateOpsItem_category :: Lens' UpdateOpsItem (Maybe Text)
updateOpsItem_category = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateOpsItem' {Maybe Text
category :: Maybe Text
$sel:category:UpdateOpsItem' :: UpdateOpsItem -> Maybe Text
category} -> Maybe Text
category) (\s :: UpdateOpsItem
s@UpdateOpsItem' {} Maybe Text
a -> UpdateOpsItem
s {$sel:category:UpdateOpsItem' :: Maybe Text
category = Maybe Text
a} :: UpdateOpsItem)

-- | Update the information about the OpsItem. Provide enough information so
-- that users reading this OpsItem for the first time understand the issue.
updateOpsItem_description :: Lens.Lens' UpdateOpsItem (Prelude.Maybe Prelude.Text)
updateOpsItem_description :: Lens' UpdateOpsItem (Maybe Text)
updateOpsItem_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateOpsItem' {Maybe Text
description :: Maybe Text
$sel:description:UpdateOpsItem' :: UpdateOpsItem -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateOpsItem
s@UpdateOpsItem' {} Maybe Text
a -> UpdateOpsItem
s {$sel:description:UpdateOpsItem' :: Maybe Text
description = Maybe Text
a} :: UpdateOpsItem)

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

-- | Add new keys or edit existing key-value pairs of the OperationalData map
-- in the OpsItem object.
--
-- 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/.
updateOpsItem_operationalData :: Lens.Lens' UpdateOpsItem (Prelude.Maybe (Prelude.HashMap Prelude.Text OpsItemDataValue))
updateOpsItem_operationalData :: Lens' UpdateOpsItem (Maybe (HashMap Text OpsItemDataValue))
updateOpsItem_operationalData = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateOpsItem' {Maybe (HashMap Text OpsItemDataValue)
operationalData :: Maybe (HashMap Text OpsItemDataValue)
$sel:operationalData:UpdateOpsItem' :: UpdateOpsItem -> Maybe (HashMap Text OpsItemDataValue)
operationalData} -> Maybe (HashMap Text OpsItemDataValue)
operationalData) (\s :: UpdateOpsItem
s@UpdateOpsItem' {} Maybe (HashMap Text OpsItemDataValue)
a -> UpdateOpsItem
s {$sel:operationalData:UpdateOpsItem' :: Maybe (HashMap Text OpsItemDataValue)
operationalData = Maybe (HashMap Text OpsItemDataValue)
a} :: UpdateOpsItem) 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

-- | Keys that you want to remove from the OperationalData map.
updateOpsItem_operationalDataToDelete :: Lens.Lens' UpdateOpsItem (Prelude.Maybe [Prelude.Text])
updateOpsItem_operationalDataToDelete :: Lens' UpdateOpsItem (Maybe [Text])
updateOpsItem_operationalDataToDelete = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateOpsItem' {Maybe [Text]
operationalDataToDelete :: Maybe [Text]
$sel:operationalDataToDelete:UpdateOpsItem' :: UpdateOpsItem -> Maybe [Text]
operationalDataToDelete} -> Maybe [Text]
operationalDataToDelete) (\s :: UpdateOpsItem
s@UpdateOpsItem' {} Maybe [Text]
a -> UpdateOpsItem
s {$sel:operationalDataToDelete:UpdateOpsItem' :: Maybe [Text]
operationalDataToDelete = Maybe [Text]
a} :: UpdateOpsItem) 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).
updateOpsItem_opsItemArn :: Lens.Lens' UpdateOpsItem (Prelude.Maybe Prelude.Text)
updateOpsItem_opsItemArn :: Lens' UpdateOpsItem (Maybe Text)
updateOpsItem_opsItemArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateOpsItem' {Maybe Text
opsItemArn :: Maybe Text
$sel:opsItemArn:UpdateOpsItem' :: UpdateOpsItem -> Maybe Text
opsItemArn} -> Maybe Text
opsItemArn) (\s :: UpdateOpsItem
s@UpdateOpsItem' {} Maybe Text
a -> UpdateOpsItem
s {$sel:opsItemArn:UpdateOpsItem' :: Maybe Text
opsItemArn = Maybe Text
a} :: UpdateOpsItem)

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

-- | One or more OpsItems that share something in common with the current
-- OpsItems. For example, related OpsItems can include OpsItems with
-- similar error messages, impacted resources, or statuses for the impacted
-- resource.
updateOpsItem_relatedOpsItems :: Lens.Lens' UpdateOpsItem (Prelude.Maybe [RelatedOpsItem])
updateOpsItem_relatedOpsItems :: Lens' UpdateOpsItem (Maybe [RelatedOpsItem])
updateOpsItem_relatedOpsItems = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateOpsItem' {Maybe [RelatedOpsItem]
relatedOpsItems :: Maybe [RelatedOpsItem]
$sel:relatedOpsItems:UpdateOpsItem' :: UpdateOpsItem -> Maybe [RelatedOpsItem]
relatedOpsItems} -> Maybe [RelatedOpsItem]
relatedOpsItems) (\s :: UpdateOpsItem
s@UpdateOpsItem' {} Maybe [RelatedOpsItem]
a -> UpdateOpsItem
s {$sel:relatedOpsItems:UpdateOpsItem' :: Maybe [RelatedOpsItem]
relatedOpsItems = Maybe [RelatedOpsItem]
a} :: UpdateOpsItem) 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

-- | Specify a new severity for an OpsItem.
updateOpsItem_severity :: Lens.Lens' UpdateOpsItem (Prelude.Maybe Prelude.Text)
updateOpsItem_severity :: Lens' UpdateOpsItem (Maybe Text)
updateOpsItem_severity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateOpsItem' {Maybe Text
severity :: Maybe Text
$sel:severity:UpdateOpsItem' :: UpdateOpsItem -> Maybe Text
severity} -> Maybe Text
severity) (\s :: UpdateOpsItem
s@UpdateOpsItem' {} Maybe Text
a -> UpdateOpsItem
s {$sel:severity:UpdateOpsItem' :: Maybe Text
severity = Maybe Text
a} :: UpdateOpsItem)

-- | 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.html#OpsCenter-working-with-OpsItems-editing-details Editing OpsItem details>
-- in the /Amazon Web Services Systems Manager User Guide/.
updateOpsItem_status :: Lens.Lens' UpdateOpsItem (Prelude.Maybe OpsItemStatus)
updateOpsItem_status :: Lens' UpdateOpsItem (Maybe OpsItemStatus)
updateOpsItem_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateOpsItem' {Maybe OpsItemStatus
status :: Maybe OpsItemStatus
$sel:status:UpdateOpsItem' :: UpdateOpsItem -> Maybe OpsItemStatus
status} -> Maybe OpsItemStatus
status) (\s :: UpdateOpsItem
s@UpdateOpsItem' {} Maybe OpsItemStatus
a -> UpdateOpsItem
s {$sel:status:UpdateOpsItem' :: Maybe OpsItemStatus
status = Maybe OpsItemStatus
a} :: UpdateOpsItem)

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

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

instance Core.AWSRequest UpdateOpsItem where
  type
    AWSResponse UpdateOpsItem =
      UpdateOpsItemResponse
  request :: (Service -> Service) -> UpdateOpsItem -> Request UpdateOpsItem
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateOpsItem
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateOpsItem)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> UpdateOpsItemResponse
UpdateOpsItemResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable UpdateOpsItem where
  hashWithSalt :: Int -> UpdateOpsItem -> Int
hashWithSalt Int
_salt UpdateOpsItem' {Maybe Natural
Maybe [Text]
Maybe [OpsItemNotification]
Maybe [RelatedOpsItem]
Maybe Text
Maybe (HashMap Text OpsItemDataValue)
Maybe POSIX
Maybe OpsItemStatus
Text
opsItemId :: Text
title :: Maybe Text
status :: Maybe OpsItemStatus
severity :: Maybe Text
relatedOpsItems :: Maybe [RelatedOpsItem]
priority :: Maybe Natural
plannedStartTime :: Maybe POSIX
plannedEndTime :: Maybe POSIX
opsItemArn :: Maybe Text
operationalDataToDelete :: Maybe [Text]
operationalData :: Maybe (HashMap Text OpsItemDataValue)
notifications :: Maybe [OpsItemNotification]
description :: Maybe Text
category :: Maybe Text
actualStartTime :: Maybe POSIX
actualEndTime :: Maybe POSIX
$sel:opsItemId:UpdateOpsItem' :: UpdateOpsItem -> Text
$sel:title:UpdateOpsItem' :: UpdateOpsItem -> Maybe Text
$sel:status:UpdateOpsItem' :: UpdateOpsItem -> Maybe OpsItemStatus
$sel:severity:UpdateOpsItem' :: UpdateOpsItem -> Maybe Text
$sel:relatedOpsItems:UpdateOpsItem' :: UpdateOpsItem -> Maybe [RelatedOpsItem]
$sel:priority:UpdateOpsItem' :: UpdateOpsItem -> Maybe Natural
$sel:plannedStartTime:UpdateOpsItem' :: UpdateOpsItem -> Maybe POSIX
$sel:plannedEndTime:UpdateOpsItem' :: UpdateOpsItem -> Maybe POSIX
$sel:opsItemArn:UpdateOpsItem' :: UpdateOpsItem -> Maybe Text
$sel:operationalDataToDelete:UpdateOpsItem' :: UpdateOpsItem -> Maybe [Text]
$sel:operationalData:UpdateOpsItem' :: UpdateOpsItem -> Maybe (HashMap Text OpsItemDataValue)
$sel:notifications:UpdateOpsItem' :: UpdateOpsItem -> Maybe [OpsItemNotification]
$sel:description:UpdateOpsItem' :: UpdateOpsItem -> Maybe Text
$sel:category:UpdateOpsItem' :: UpdateOpsItem -> Maybe Text
$sel:actualStartTime:UpdateOpsItem' :: UpdateOpsItem -> Maybe POSIX
$sel:actualEndTime:UpdateOpsItem' :: UpdateOpsItem -> 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
description
      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]
operationalDataToDelete
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
opsItemArn
      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 OpsItemStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
title
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
opsItemId

instance Prelude.NFData UpdateOpsItem where
  rnf :: UpdateOpsItem -> ()
rnf UpdateOpsItem' {Maybe Natural
Maybe [Text]
Maybe [OpsItemNotification]
Maybe [RelatedOpsItem]
Maybe Text
Maybe (HashMap Text OpsItemDataValue)
Maybe POSIX
Maybe OpsItemStatus
Text
opsItemId :: Text
title :: Maybe Text
status :: Maybe OpsItemStatus
severity :: Maybe Text
relatedOpsItems :: Maybe [RelatedOpsItem]
priority :: Maybe Natural
plannedStartTime :: Maybe POSIX
plannedEndTime :: Maybe POSIX
opsItemArn :: Maybe Text
operationalDataToDelete :: Maybe [Text]
operationalData :: Maybe (HashMap Text OpsItemDataValue)
notifications :: Maybe [OpsItemNotification]
description :: Maybe Text
category :: Maybe Text
actualStartTime :: Maybe POSIX
actualEndTime :: Maybe POSIX
$sel:opsItemId:UpdateOpsItem' :: UpdateOpsItem -> Text
$sel:title:UpdateOpsItem' :: UpdateOpsItem -> Maybe Text
$sel:status:UpdateOpsItem' :: UpdateOpsItem -> Maybe OpsItemStatus
$sel:severity:UpdateOpsItem' :: UpdateOpsItem -> Maybe Text
$sel:relatedOpsItems:UpdateOpsItem' :: UpdateOpsItem -> Maybe [RelatedOpsItem]
$sel:priority:UpdateOpsItem' :: UpdateOpsItem -> Maybe Natural
$sel:plannedStartTime:UpdateOpsItem' :: UpdateOpsItem -> Maybe POSIX
$sel:plannedEndTime:UpdateOpsItem' :: UpdateOpsItem -> Maybe POSIX
$sel:opsItemArn:UpdateOpsItem' :: UpdateOpsItem -> Maybe Text
$sel:operationalDataToDelete:UpdateOpsItem' :: UpdateOpsItem -> Maybe [Text]
$sel:operationalData:UpdateOpsItem' :: UpdateOpsItem -> Maybe (HashMap Text OpsItemDataValue)
$sel:notifications:UpdateOpsItem' :: UpdateOpsItem -> Maybe [OpsItemNotification]
$sel:description:UpdateOpsItem' :: UpdateOpsItem -> Maybe Text
$sel:category:UpdateOpsItem' :: UpdateOpsItem -> Maybe Text
$sel:actualStartTime:UpdateOpsItem' :: UpdateOpsItem -> Maybe POSIX
$sel:actualEndTime:UpdateOpsItem' :: UpdateOpsItem -> 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
description
      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]
operationalDataToDelete
      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 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 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 Text
opsItemId

instance Data.ToHeaders UpdateOpsItem where
  toHeaders :: UpdateOpsItem -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# (ByteString
"AmazonSSM.UpdateOpsItem" :: Prelude.ByteString),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateOpsItem where
  toJSON :: UpdateOpsItem -> Value
toJSON UpdateOpsItem' {Maybe Natural
Maybe [Text]
Maybe [OpsItemNotification]
Maybe [RelatedOpsItem]
Maybe Text
Maybe (HashMap Text OpsItemDataValue)
Maybe POSIX
Maybe OpsItemStatus
Text
opsItemId :: Text
title :: Maybe Text
status :: Maybe OpsItemStatus
severity :: Maybe Text
relatedOpsItems :: Maybe [RelatedOpsItem]
priority :: Maybe Natural
plannedStartTime :: Maybe POSIX
plannedEndTime :: Maybe POSIX
opsItemArn :: Maybe Text
operationalDataToDelete :: Maybe [Text]
operationalData :: Maybe (HashMap Text OpsItemDataValue)
notifications :: Maybe [OpsItemNotification]
description :: Maybe Text
category :: Maybe Text
actualStartTime :: Maybe POSIX
actualEndTime :: Maybe POSIX
$sel:opsItemId:UpdateOpsItem' :: UpdateOpsItem -> Text
$sel:title:UpdateOpsItem' :: UpdateOpsItem -> Maybe Text
$sel:status:UpdateOpsItem' :: UpdateOpsItem -> Maybe OpsItemStatus
$sel:severity:UpdateOpsItem' :: UpdateOpsItem -> Maybe Text
$sel:relatedOpsItems:UpdateOpsItem' :: UpdateOpsItem -> Maybe [RelatedOpsItem]
$sel:priority:UpdateOpsItem' :: UpdateOpsItem -> Maybe Natural
$sel:plannedStartTime:UpdateOpsItem' :: UpdateOpsItem -> Maybe POSIX
$sel:plannedEndTime:UpdateOpsItem' :: UpdateOpsItem -> Maybe POSIX
$sel:opsItemArn:UpdateOpsItem' :: UpdateOpsItem -> Maybe Text
$sel:operationalDataToDelete:UpdateOpsItem' :: UpdateOpsItem -> Maybe [Text]
$sel:operationalData:UpdateOpsItem' :: UpdateOpsItem -> Maybe (HashMap Text OpsItemDataValue)
$sel:notifications:UpdateOpsItem' :: UpdateOpsItem -> Maybe [OpsItemNotification]
$sel:description:UpdateOpsItem' :: UpdateOpsItem -> Maybe Text
$sel:category:UpdateOpsItem' :: UpdateOpsItem -> Maybe Text
$sel:actualStartTime:UpdateOpsItem' :: UpdateOpsItem -> Maybe POSIX
$sel:actualEndTime:UpdateOpsItem' :: UpdateOpsItem -> Maybe POSIX
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ActualEndTime" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe POSIX
actualEndTime,
            (Key
"ActualStartTime" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe POSIX
actualStartTime,
            (Key
"Category" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
category,
            (Key
"Description" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
description,
            (Key
"Notifications" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [OpsItemNotification]
notifications,
            (Key
"OperationalData" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (HashMap Text OpsItemDataValue)
operationalData,
            (Key
"OperationalDataToDelete" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
operationalDataToDelete,
            (Key
"OpsItemArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
opsItemArn,
            (Key
"PlannedEndTime" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe POSIX
plannedEndTime,
            (Key
"PlannedStartTime" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe POSIX
plannedStartTime,
            (Key
"Priority" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
priority,
            (Key
"RelatedOpsItems" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [RelatedOpsItem]
relatedOpsItems,
            (Key
"Severity" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
severity,
            (Key
"Status" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe OpsItemStatus
status,
            (Key
"Title" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
title,
            forall a. a -> Maybe a
Prelude.Just (Key
"OpsItemId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
opsItemId)
          ]
      )

instance Data.ToPath UpdateOpsItem where
  toPath :: UpdateOpsItem -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery UpdateOpsItem where
  toQuery :: UpdateOpsItem -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newUpdateOpsItemResponse' smart constructor.
data UpdateOpsItemResponse = UpdateOpsItemResponse'
  { -- | The response's http status code.
    UpdateOpsItemResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateOpsItemResponse -> UpdateOpsItemResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateOpsItemResponse -> UpdateOpsItemResponse -> Bool
$c/= :: UpdateOpsItemResponse -> UpdateOpsItemResponse -> Bool
== :: UpdateOpsItemResponse -> UpdateOpsItemResponse -> Bool
$c== :: UpdateOpsItemResponse -> UpdateOpsItemResponse -> Bool
Prelude.Eq, ReadPrec [UpdateOpsItemResponse]
ReadPrec UpdateOpsItemResponse
Int -> ReadS UpdateOpsItemResponse
ReadS [UpdateOpsItemResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateOpsItemResponse]
$creadListPrec :: ReadPrec [UpdateOpsItemResponse]
readPrec :: ReadPrec UpdateOpsItemResponse
$creadPrec :: ReadPrec UpdateOpsItemResponse
readList :: ReadS [UpdateOpsItemResponse]
$creadList :: ReadS [UpdateOpsItemResponse]
readsPrec :: Int -> ReadS UpdateOpsItemResponse
$creadsPrec :: Int -> ReadS UpdateOpsItemResponse
Prelude.Read, Int -> UpdateOpsItemResponse -> ShowS
[UpdateOpsItemResponse] -> ShowS
UpdateOpsItemResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateOpsItemResponse] -> ShowS
$cshowList :: [UpdateOpsItemResponse] -> ShowS
show :: UpdateOpsItemResponse -> String
$cshow :: UpdateOpsItemResponse -> String
showsPrec :: Int -> UpdateOpsItemResponse -> ShowS
$cshowsPrec :: Int -> UpdateOpsItemResponse -> ShowS
Prelude.Show, forall x. Rep UpdateOpsItemResponse x -> UpdateOpsItemResponse
forall x. UpdateOpsItemResponse -> Rep UpdateOpsItemResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateOpsItemResponse x -> UpdateOpsItemResponse
$cfrom :: forall x. UpdateOpsItemResponse -> Rep UpdateOpsItemResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateOpsItemResponse' 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:
--
-- 'httpStatus', 'updateOpsItemResponse_httpStatus' - The response's http status code.
newUpdateOpsItemResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateOpsItemResponse
newUpdateOpsItemResponse :: Int -> UpdateOpsItemResponse
newUpdateOpsItemResponse Int
pHttpStatus_ =
  UpdateOpsItemResponse' {$sel:httpStatus:UpdateOpsItemResponse' :: Int
httpStatus = Int
pHttpStatus_}

-- | The response's http status code.
updateOpsItemResponse_httpStatus :: Lens.Lens' UpdateOpsItemResponse Prelude.Int
updateOpsItemResponse_httpStatus :: Lens' UpdateOpsItemResponse Int
updateOpsItemResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateOpsItemResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateOpsItemResponse' :: UpdateOpsItemResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdateOpsItemResponse
s@UpdateOpsItemResponse' {} Int
a -> UpdateOpsItemResponse
s {$sel:httpStatus:UpdateOpsItemResponse' :: Int
httpStatus = Int
a} :: UpdateOpsItemResponse)

instance Prelude.NFData UpdateOpsItemResponse where
  rnf :: UpdateOpsItemResponse -> ()
rnf UpdateOpsItemResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateOpsItemResponse' :: UpdateOpsItemResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus