{-# 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.Kafka.Types.ClusterOperationInfo
-- 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.Kafka.Types.ClusterOperationInfo where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Kafka.Types.ClusterOperationStep
import Amazonka.Kafka.Types.ErrorInfo
import Amazonka.Kafka.Types.MutableClusterInfo
import qualified Amazonka.Prelude as Prelude

-- | Returns information about a cluster operation.
--
-- /See:/ 'newClusterOperationInfo' smart constructor.
data ClusterOperationInfo = ClusterOperationInfo'
  { -- | The ID of the API request that triggered this operation.
    ClusterOperationInfo -> Maybe Text
clientRequestId :: Prelude.Maybe Prelude.Text,
    -- | ARN of the cluster.
    ClusterOperationInfo -> Maybe Text
clusterArn :: Prelude.Maybe Prelude.Text,
    -- | The time that the operation was created.
    ClusterOperationInfo -> Maybe ISO8601
creationTime :: Prelude.Maybe Data.ISO8601,
    -- | The time at which the operation finished.
    ClusterOperationInfo -> Maybe ISO8601
endTime :: Prelude.Maybe Data.ISO8601,
    -- | Describes the error if the operation fails.
    ClusterOperationInfo -> Maybe ErrorInfo
errorInfo :: Prelude.Maybe ErrorInfo,
    -- | ARN of the cluster operation.
    ClusterOperationInfo -> Maybe Text
operationArn :: Prelude.Maybe Prelude.Text,
    -- | State of the cluster operation.
    ClusterOperationInfo -> Maybe Text
operationState :: Prelude.Maybe Prelude.Text,
    -- | Steps completed during the operation.
    ClusterOperationInfo -> Maybe [ClusterOperationStep]
operationSteps :: Prelude.Maybe [ClusterOperationStep],
    -- | Type of the cluster operation.
    ClusterOperationInfo -> Maybe Text
operationType :: Prelude.Maybe Prelude.Text,
    -- | Information about cluster attributes before a cluster is updated.
    ClusterOperationInfo -> Maybe MutableClusterInfo
sourceClusterInfo :: Prelude.Maybe MutableClusterInfo,
    -- | Information about cluster attributes after a cluster is updated.
    ClusterOperationInfo -> Maybe MutableClusterInfo
targetClusterInfo :: Prelude.Maybe MutableClusterInfo
  }
  deriving (ClusterOperationInfo -> ClusterOperationInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClusterOperationInfo -> ClusterOperationInfo -> Bool
$c/= :: ClusterOperationInfo -> ClusterOperationInfo -> Bool
== :: ClusterOperationInfo -> ClusterOperationInfo -> Bool
$c== :: ClusterOperationInfo -> ClusterOperationInfo -> Bool
Prelude.Eq, ReadPrec [ClusterOperationInfo]
ReadPrec ClusterOperationInfo
Int -> ReadS ClusterOperationInfo
ReadS [ClusterOperationInfo]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ClusterOperationInfo]
$creadListPrec :: ReadPrec [ClusterOperationInfo]
readPrec :: ReadPrec ClusterOperationInfo
$creadPrec :: ReadPrec ClusterOperationInfo
readList :: ReadS [ClusterOperationInfo]
$creadList :: ReadS [ClusterOperationInfo]
readsPrec :: Int -> ReadS ClusterOperationInfo
$creadsPrec :: Int -> ReadS ClusterOperationInfo
Prelude.Read, Int -> ClusterOperationInfo -> ShowS
[ClusterOperationInfo] -> ShowS
ClusterOperationInfo -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClusterOperationInfo] -> ShowS
$cshowList :: [ClusterOperationInfo] -> ShowS
show :: ClusterOperationInfo -> String
$cshow :: ClusterOperationInfo -> String
showsPrec :: Int -> ClusterOperationInfo -> ShowS
$cshowsPrec :: Int -> ClusterOperationInfo -> ShowS
Prelude.Show, forall x. Rep ClusterOperationInfo x -> ClusterOperationInfo
forall x. ClusterOperationInfo -> Rep ClusterOperationInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ClusterOperationInfo x -> ClusterOperationInfo
$cfrom :: forall x. ClusterOperationInfo -> Rep ClusterOperationInfo x
Prelude.Generic)

-- |
-- Create a value of 'ClusterOperationInfo' 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:
--
-- 'clientRequestId', 'clusterOperationInfo_clientRequestId' - The ID of the API request that triggered this operation.
--
-- 'clusterArn', 'clusterOperationInfo_clusterArn' - ARN of the cluster.
--
-- 'creationTime', 'clusterOperationInfo_creationTime' - The time that the operation was created.
--
-- 'endTime', 'clusterOperationInfo_endTime' - The time at which the operation finished.
--
-- 'errorInfo', 'clusterOperationInfo_errorInfo' - Describes the error if the operation fails.
--
-- 'operationArn', 'clusterOperationInfo_operationArn' - ARN of the cluster operation.
--
-- 'operationState', 'clusterOperationInfo_operationState' - State of the cluster operation.
--
-- 'operationSteps', 'clusterOperationInfo_operationSteps' - Steps completed during the operation.
--
-- 'operationType', 'clusterOperationInfo_operationType' - Type of the cluster operation.
--
-- 'sourceClusterInfo', 'clusterOperationInfo_sourceClusterInfo' - Information about cluster attributes before a cluster is updated.
--
-- 'targetClusterInfo', 'clusterOperationInfo_targetClusterInfo' - Information about cluster attributes after a cluster is updated.
newClusterOperationInfo ::
  ClusterOperationInfo
newClusterOperationInfo :: ClusterOperationInfo
newClusterOperationInfo =
  ClusterOperationInfo'
    { $sel:clientRequestId:ClusterOperationInfo' :: Maybe Text
clientRequestId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:clusterArn:ClusterOperationInfo' :: Maybe Text
clusterArn = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:ClusterOperationInfo' :: Maybe ISO8601
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:endTime:ClusterOperationInfo' :: Maybe ISO8601
endTime = forall a. Maybe a
Prelude.Nothing,
      $sel:errorInfo:ClusterOperationInfo' :: Maybe ErrorInfo
errorInfo = forall a. Maybe a
Prelude.Nothing,
      $sel:operationArn:ClusterOperationInfo' :: Maybe Text
operationArn = forall a. Maybe a
Prelude.Nothing,
      $sel:operationState:ClusterOperationInfo' :: Maybe Text
operationState = forall a. Maybe a
Prelude.Nothing,
      $sel:operationSteps:ClusterOperationInfo' :: Maybe [ClusterOperationStep]
operationSteps = forall a. Maybe a
Prelude.Nothing,
      $sel:operationType:ClusterOperationInfo' :: Maybe Text
operationType = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceClusterInfo:ClusterOperationInfo' :: Maybe MutableClusterInfo
sourceClusterInfo = forall a. Maybe a
Prelude.Nothing,
      $sel:targetClusterInfo:ClusterOperationInfo' :: Maybe MutableClusterInfo
targetClusterInfo = forall a. Maybe a
Prelude.Nothing
    }

-- | The ID of the API request that triggered this operation.
clusterOperationInfo_clientRequestId :: Lens.Lens' ClusterOperationInfo (Prelude.Maybe Prelude.Text)
clusterOperationInfo_clientRequestId :: Lens' ClusterOperationInfo (Maybe Text)
clusterOperationInfo_clientRequestId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterOperationInfo' {Maybe Text
clientRequestId :: Maybe Text
$sel:clientRequestId:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe Text
clientRequestId} -> Maybe Text
clientRequestId) (\s :: ClusterOperationInfo
s@ClusterOperationInfo' {} Maybe Text
a -> ClusterOperationInfo
s {$sel:clientRequestId:ClusterOperationInfo' :: Maybe Text
clientRequestId = Maybe Text
a} :: ClusterOperationInfo)

-- | ARN of the cluster.
clusterOperationInfo_clusterArn :: Lens.Lens' ClusterOperationInfo (Prelude.Maybe Prelude.Text)
clusterOperationInfo_clusterArn :: Lens' ClusterOperationInfo (Maybe Text)
clusterOperationInfo_clusterArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterOperationInfo' {Maybe Text
clusterArn :: Maybe Text
$sel:clusterArn:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe Text
clusterArn} -> Maybe Text
clusterArn) (\s :: ClusterOperationInfo
s@ClusterOperationInfo' {} Maybe Text
a -> ClusterOperationInfo
s {$sel:clusterArn:ClusterOperationInfo' :: Maybe Text
clusterArn = Maybe Text
a} :: ClusterOperationInfo)

-- | The time that the operation was created.
clusterOperationInfo_creationTime :: Lens.Lens' ClusterOperationInfo (Prelude.Maybe Prelude.UTCTime)
clusterOperationInfo_creationTime :: Lens' ClusterOperationInfo (Maybe UTCTime)
clusterOperationInfo_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterOperationInfo' {Maybe ISO8601
creationTime :: Maybe ISO8601
$sel:creationTime:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe ISO8601
creationTime} -> Maybe ISO8601
creationTime) (\s :: ClusterOperationInfo
s@ClusterOperationInfo' {} Maybe ISO8601
a -> ClusterOperationInfo
s {$sel:creationTime:ClusterOperationInfo' :: Maybe ISO8601
creationTime = Maybe ISO8601
a} :: ClusterOperationInfo) 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 at which the operation finished.
clusterOperationInfo_endTime :: Lens.Lens' ClusterOperationInfo (Prelude.Maybe Prelude.UTCTime)
clusterOperationInfo_endTime :: Lens' ClusterOperationInfo (Maybe UTCTime)
clusterOperationInfo_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterOperationInfo' {Maybe ISO8601
endTime :: Maybe ISO8601
$sel:endTime:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe ISO8601
endTime} -> Maybe ISO8601
endTime) (\s :: ClusterOperationInfo
s@ClusterOperationInfo' {} Maybe ISO8601
a -> ClusterOperationInfo
s {$sel:endTime:ClusterOperationInfo' :: Maybe ISO8601
endTime = Maybe ISO8601
a} :: ClusterOperationInfo) 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

-- | Describes the error if the operation fails.
clusterOperationInfo_errorInfo :: Lens.Lens' ClusterOperationInfo (Prelude.Maybe ErrorInfo)
clusterOperationInfo_errorInfo :: Lens' ClusterOperationInfo (Maybe ErrorInfo)
clusterOperationInfo_errorInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterOperationInfo' {Maybe ErrorInfo
errorInfo :: Maybe ErrorInfo
$sel:errorInfo:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe ErrorInfo
errorInfo} -> Maybe ErrorInfo
errorInfo) (\s :: ClusterOperationInfo
s@ClusterOperationInfo' {} Maybe ErrorInfo
a -> ClusterOperationInfo
s {$sel:errorInfo:ClusterOperationInfo' :: Maybe ErrorInfo
errorInfo = Maybe ErrorInfo
a} :: ClusterOperationInfo)

-- | ARN of the cluster operation.
clusterOperationInfo_operationArn :: Lens.Lens' ClusterOperationInfo (Prelude.Maybe Prelude.Text)
clusterOperationInfo_operationArn :: Lens' ClusterOperationInfo (Maybe Text)
clusterOperationInfo_operationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterOperationInfo' {Maybe Text
operationArn :: Maybe Text
$sel:operationArn:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe Text
operationArn} -> Maybe Text
operationArn) (\s :: ClusterOperationInfo
s@ClusterOperationInfo' {} Maybe Text
a -> ClusterOperationInfo
s {$sel:operationArn:ClusterOperationInfo' :: Maybe Text
operationArn = Maybe Text
a} :: ClusterOperationInfo)

-- | State of the cluster operation.
clusterOperationInfo_operationState :: Lens.Lens' ClusterOperationInfo (Prelude.Maybe Prelude.Text)
clusterOperationInfo_operationState :: Lens' ClusterOperationInfo (Maybe Text)
clusterOperationInfo_operationState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterOperationInfo' {Maybe Text
operationState :: Maybe Text
$sel:operationState:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe Text
operationState} -> Maybe Text
operationState) (\s :: ClusterOperationInfo
s@ClusterOperationInfo' {} Maybe Text
a -> ClusterOperationInfo
s {$sel:operationState:ClusterOperationInfo' :: Maybe Text
operationState = Maybe Text
a} :: ClusterOperationInfo)

-- | Steps completed during the operation.
clusterOperationInfo_operationSteps :: Lens.Lens' ClusterOperationInfo (Prelude.Maybe [ClusterOperationStep])
clusterOperationInfo_operationSteps :: Lens' ClusterOperationInfo (Maybe [ClusterOperationStep])
clusterOperationInfo_operationSteps = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterOperationInfo' {Maybe [ClusterOperationStep]
operationSteps :: Maybe [ClusterOperationStep]
$sel:operationSteps:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe [ClusterOperationStep]
operationSteps} -> Maybe [ClusterOperationStep]
operationSteps) (\s :: ClusterOperationInfo
s@ClusterOperationInfo' {} Maybe [ClusterOperationStep]
a -> ClusterOperationInfo
s {$sel:operationSteps:ClusterOperationInfo' :: Maybe [ClusterOperationStep]
operationSteps = Maybe [ClusterOperationStep]
a} :: ClusterOperationInfo) 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

-- | Type of the cluster operation.
clusterOperationInfo_operationType :: Lens.Lens' ClusterOperationInfo (Prelude.Maybe Prelude.Text)
clusterOperationInfo_operationType :: Lens' ClusterOperationInfo (Maybe Text)
clusterOperationInfo_operationType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterOperationInfo' {Maybe Text
operationType :: Maybe Text
$sel:operationType:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe Text
operationType} -> Maybe Text
operationType) (\s :: ClusterOperationInfo
s@ClusterOperationInfo' {} Maybe Text
a -> ClusterOperationInfo
s {$sel:operationType:ClusterOperationInfo' :: Maybe Text
operationType = Maybe Text
a} :: ClusterOperationInfo)

-- | Information about cluster attributes before a cluster is updated.
clusterOperationInfo_sourceClusterInfo :: Lens.Lens' ClusterOperationInfo (Prelude.Maybe MutableClusterInfo)
clusterOperationInfo_sourceClusterInfo :: Lens' ClusterOperationInfo (Maybe MutableClusterInfo)
clusterOperationInfo_sourceClusterInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterOperationInfo' {Maybe MutableClusterInfo
sourceClusterInfo :: Maybe MutableClusterInfo
$sel:sourceClusterInfo:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe MutableClusterInfo
sourceClusterInfo} -> Maybe MutableClusterInfo
sourceClusterInfo) (\s :: ClusterOperationInfo
s@ClusterOperationInfo' {} Maybe MutableClusterInfo
a -> ClusterOperationInfo
s {$sel:sourceClusterInfo:ClusterOperationInfo' :: Maybe MutableClusterInfo
sourceClusterInfo = Maybe MutableClusterInfo
a} :: ClusterOperationInfo)

-- | Information about cluster attributes after a cluster is updated.
clusterOperationInfo_targetClusterInfo :: Lens.Lens' ClusterOperationInfo (Prelude.Maybe MutableClusterInfo)
clusterOperationInfo_targetClusterInfo :: Lens' ClusterOperationInfo (Maybe MutableClusterInfo)
clusterOperationInfo_targetClusterInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClusterOperationInfo' {Maybe MutableClusterInfo
targetClusterInfo :: Maybe MutableClusterInfo
$sel:targetClusterInfo:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe MutableClusterInfo
targetClusterInfo} -> Maybe MutableClusterInfo
targetClusterInfo) (\s :: ClusterOperationInfo
s@ClusterOperationInfo' {} Maybe MutableClusterInfo
a -> ClusterOperationInfo
s {$sel:targetClusterInfo:ClusterOperationInfo' :: Maybe MutableClusterInfo
targetClusterInfo = Maybe MutableClusterInfo
a} :: ClusterOperationInfo)

instance Data.FromJSON ClusterOperationInfo where
  parseJSON :: Value -> Parser ClusterOperationInfo
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ClusterOperationInfo"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe ISO8601
-> Maybe ISO8601
-> Maybe ErrorInfo
-> Maybe Text
-> Maybe Text
-> Maybe [ClusterOperationStep]
-> Maybe Text
-> Maybe MutableClusterInfo
-> Maybe MutableClusterInfo
-> ClusterOperationInfo
ClusterOperationInfo'
            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
"clientRequestId")
            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
"clusterArn")
            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
"creationTime")
            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
"endTime")
            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
"errorInfo")
            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
"operationArn")
            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
"operationState")
            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
"operationSteps" 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
"operationType")
            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
"sourceClusterInfo")
            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
"targetClusterInfo")
      )

instance Prelude.Hashable ClusterOperationInfo where
  hashWithSalt :: Int -> ClusterOperationInfo -> Int
hashWithSalt Int
_salt ClusterOperationInfo' {Maybe [ClusterOperationStep]
Maybe Text
Maybe ISO8601
Maybe ErrorInfo
Maybe MutableClusterInfo
targetClusterInfo :: Maybe MutableClusterInfo
sourceClusterInfo :: Maybe MutableClusterInfo
operationType :: Maybe Text
operationSteps :: Maybe [ClusterOperationStep]
operationState :: Maybe Text
operationArn :: Maybe Text
errorInfo :: Maybe ErrorInfo
endTime :: Maybe ISO8601
creationTime :: Maybe ISO8601
clusterArn :: Maybe Text
clientRequestId :: Maybe Text
$sel:targetClusterInfo:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe MutableClusterInfo
$sel:sourceClusterInfo:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe MutableClusterInfo
$sel:operationType:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe Text
$sel:operationSteps:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe [ClusterOperationStep]
$sel:operationState:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe Text
$sel:operationArn:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe Text
$sel:errorInfo:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe ErrorInfo
$sel:endTime:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe ISO8601
$sel:creationTime:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe ISO8601
$sel:clusterArn:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe Text
$sel:clientRequestId:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientRequestId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clusterArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
creationTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
endTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ErrorInfo
errorInfo
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
operationArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
operationState
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ClusterOperationStep]
operationSteps
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
operationType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MutableClusterInfo
sourceClusterInfo
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MutableClusterInfo
targetClusterInfo

instance Prelude.NFData ClusterOperationInfo where
  rnf :: ClusterOperationInfo -> ()
rnf ClusterOperationInfo' {Maybe [ClusterOperationStep]
Maybe Text
Maybe ISO8601
Maybe ErrorInfo
Maybe MutableClusterInfo
targetClusterInfo :: Maybe MutableClusterInfo
sourceClusterInfo :: Maybe MutableClusterInfo
operationType :: Maybe Text
operationSteps :: Maybe [ClusterOperationStep]
operationState :: Maybe Text
operationArn :: Maybe Text
errorInfo :: Maybe ErrorInfo
endTime :: Maybe ISO8601
creationTime :: Maybe ISO8601
clusterArn :: Maybe Text
clientRequestId :: Maybe Text
$sel:targetClusterInfo:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe MutableClusterInfo
$sel:sourceClusterInfo:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe MutableClusterInfo
$sel:operationType:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe Text
$sel:operationSteps:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe [ClusterOperationStep]
$sel:operationState:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe Text
$sel:operationArn:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe Text
$sel:errorInfo:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe ErrorInfo
$sel:endTime:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe ISO8601
$sel:creationTime:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe ISO8601
$sel:clusterArn:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe Text
$sel:clientRequestId:ClusterOperationInfo' :: ClusterOperationInfo -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientRequestId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clusterArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
endTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ErrorInfo
errorInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
operationArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
operationState
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ClusterOperationStep]
operationSteps
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
operationType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MutableClusterInfo
sourceClusterInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MutableClusterInfo
targetClusterInfo