{-# 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.Route53AutoNaming.Types.Operation
-- 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.Route53AutoNaming.Types.Operation 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.Route53AutoNaming.Types.OperationStatus
import Amazonka.Route53AutoNaming.Types.OperationTargetType
import Amazonka.Route53AutoNaming.Types.OperationType

-- | A complex type that contains information about a specified operation.
--
-- /See:/ 'newOperation' smart constructor.
data Operation = Operation'
  { -- | The date and time that the request was submitted, in Unix date\/time
    -- format and Coordinated Universal Time (UTC). The value of @CreateDate@
    -- is accurate to milliseconds. For example, the value @1516925490.087@
    -- represents Friday, January 26, 2018 12:11:30.087 AM.
    Operation -> Maybe POSIX
createDate :: Prelude.Maybe Data.POSIX,
    -- | The code associated with @ErrorMessage@. Values for @ErrorCode@ include
    -- the following:
    --
    -- -   @ACCESS_DENIED@
    --
    -- -   @CANNOT_CREATE_HOSTED_ZONE@
    --
    -- -   @EXPIRED_TOKEN@
    --
    -- -   @HOSTED_ZONE_NOT_FOUND@
    --
    -- -   @INTERNAL_FAILURE@
    --
    -- -   @INVALID_CHANGE_BATCH@
    --
    -- -   @THROTTLED_REQUEST@
    Operation -> Maybe Text
errorCode :: Prelude.Maybe Prelude.Text,
    -- | If the value of @Status@ is @FAIL@, the reason that the operation
    -- failed.
    Operation -> Maybe Text
errorMessage :: Prelude.Maybe Prelude.Text,
    -- | The ID of the operation that you want to get information about.
    Operation -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The status of the operation. Values include the following:
    --
    -- [SUBMITTED]
    --     This is the initial state that occurs immediately after you submit a
    --     request.
    --
    -- [PENDING]
    --     Cloud Map is performing the operation.
    --
    -- [SUCCESS]
    --     The operation succeeded.
    --
    -- [FAIL]
    --     The operation failed. For the failure reason, see @ErrorMessage@.
    Operation -> Maybe OperationStatus
status :: Prelude.Maybe OperationStatus,
    -- | The name of the target entity that\'s associated with the operation:
    --
    -- [NAMESPACE]
    --     The namespace ID is returned in the @ResourceId@ property.
    --
    -- [SERVICE]
    --     The service ID is returned in the @ResourceId@ property.
    --
    -- [INSTANCE]
    --     The instance ID is returned in the @ResourceId@ property.
    Operation -> Maybe (HashMap OperationTargetType Text)
targets :: Prelude.Maybe (Prelude.HashMap OperationTargetType Prelude.Text),
    -- | The name of the operation that\'s associated with the specified ID.
    Operation -> Maybe OperationType
type' :: Prelude.Maybe OperationType,
    -- | The date and time that the value of @Status@ changed to the current
    -- value, in Unix date\/time format and Coordinated Universal Time (UTC).
    -- The value of @UpdateDate@ is accurate to milliseconds. For example, the
    -- value @1516925490.087@ represents Friday, January 26, 2018 12:11:30.087
    -- AM.
    Operation -> Maybe POSIX
updateDate :: Prelude.Maybe Data.POSIX
  }
  deriving (Operation -> Operation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Operation -> Operation -> Bool
$c/= :: Operation -> Operation -> Bool
== :: Operation -> Operation -> Bool
$c== :: Operation -> Operation -> Bool
Prelude.Eq, ReadPrec [Operation]
ReadPrec Operation
Int -> ReadS Operation
ReadS [Operation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Operation]
$creadListPrec :: ReadPrec [Operation]
readPrec :: ReadPrec Operation
$creadPrec :: ReadPrec Operation
readList :: ReadS [Operation]
$creadList :: ReadS [Operation]
readsPrec :: Int -> ReadS Operation
$creadsPrec :: Int -> ReadS Operation
Prelude.Read, Int -> Operation -> ShowS
[Operation] -> ShowS
Operation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Operation] -> ShowS
$cshowList :: [Operation] -> ShowS
show :: Operation -> String
$cshow :: Operation -> String
showsPrec :: Int -> Operation -> ShowS
$cshowsPrec :: Int -> Operation -> ShowS
Prelude.Show, forall x. Rep Operation x -> Operation
forall x. Operation -> Rep Operation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Operation x -> Operation
$cfrom :: forall x. Operation -> Rep Operation x
Prelude.Generic)

-- |
-- Create a value of 'Operation' 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:
--
-- 'createDate', 'operation_createDate' - The date and time that the request was submitted, in Unix date\/time
-- format and Coordinated Universal Time (UTC). The value of @CreateDate@
-- is accurate to milliseconds. For example, the value @1516925490.087@
-- represents Friday, January 26, 2018 12:11:30.087 AM.
--
-- 'errorCode', 'operation_errorCode' - The code associated with @ErrorMessage@. Values for @ErrorCode@ include
-- the following:
--
-- -   @ACCESS_DENIED@
--
-- -   @CANNOT_CREATE_HOSTED_ZONE@
--
-- -   @EXPIRED_TOKEN@
--
-- -   @HOSTED_ZONE_NOT_FOUND@
--
-- -   @INTERNAL_FAILURE@
--
-- -   @INVALID_CHANGE_BATCH@
--
-- -   @THROTTLED_REQUEST@
--
-- 'errorMessage', 'operation_errorMessage' - If the value of @Status@ is @FAIL@, the reason that the operation
-- failed.
--
-- 'id', 'operation_id' - The ID of the operation that you want to get information about.
--
-- 'status', 'operation_status' - The status of the operation. Values include the following:
--
-- [SUBMITTED]
--     This is the initial state that occurs immediately after you submit a
--     request.
--
-- [PENDING]
--     Cloud Map is performing the operation.
--
-- [SUCCESS]
--     The operation succeeded.
--
-- [FAIL]
--     The operation failed. For the failure reason, see @ErrorMessage@.
--
-- 'targets', 'operation_targets' - The name of the target entity that\'s associated with the operation:
--
-- [NAMESPACE]
--     The namespace ID is returned in the @ResourceId@ property.
--
-- [SERVICE]
--     The service ID is returned in the @ResourceId@ property.
--
-- [INSTANCE]
--     The instance ID is returned in the @ResourceId@ property.
--
-- 'type'', 'operation_type' - The name of the operation that\'s associated with the specified ID.
--
-- 'updateDate', 'operation_updateDate' - The date and time that the value of @Status@ changed to the current
-- value, in Unix date\/time format and Coordinated Universal Time (UTC).
-- The value of @UpdateDate@ is accurate to milliseconds. For example, the
-- value @1516925490.087@ represents Friday, January 26, 2018 12:11:30.087
-- AM.
newOperation ::
  Operation
newOperation :: Operation
newOperation =
  Operation'
    { $sel:createDate:Operation' :: Maybe POSIX
createDate = forall a. Maybe a
Prelude.Nothing,
      $sel:errorCode:Operation' :: Maybe Text
errorCode = forall a. Maybe a
Prelude.Nothing,
      $sel:errorMessage:Operation' :: Maybe Text
errorMessage = forall a. Maybe a
Prelude.Nothing,
      $sel:id:Operation' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:status:Operation' :: Maybe OperationStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:targets:Operation' :: Maybe (HashMap OperationTargetType Text)
targets = forall a. Maybe a
Prelude.Nothing,
      $sel:type':Operation' :: Maybe OperationType
type' = forall a. Maybe a
Prelude.Nothing,
      $sel:updateDate:Operation' :: Maybe POSIX
updateDate = forall a. Maybe a
Prelude.Nothing
    }

-- | The date and time that the request was submitted, in Unix date\/time
-- format and Coordinated Universal Time (UTC). The value of @CreateDate@
-- is accurate to milliseconds. For example, the value @1516925490.087@
-- represents Friday, January 26, 2018 12:11:30.087 AM.
operation_createDate :: Lens.Lens' Operation (Prelude.Maybe Prelude.UTCTime)
operation_createDate :: Lens' Operation (Maybe UTCTime)
operation_createDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Operation' {Maybe POSIX
createDate :: Maybe POSIX
$sel:createDate:Operation' :: Operation -> Maybe POSIX
createDate} -> Maybe POSIX
createDate) (\s :: Operation
s@Operation' {} Maybe POSIX
a -> Operation
s {$sel:createDate:Operation' :: Maybe POSIX
createDate = Maybe POSIX
a} :: Operation) 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 code associated with @ErrorMessage@. Values for @ErrorCode@ include
-- the following:
--
-- -   @ACCESS_DENIED@
--
-- -   @CANNOT_CREATE_HOSTED_ZONE@
--
-- -   @EXPIRED_TOKEN@
--
-- -   @HOSTED_ZONE_NOT_FOUND@
--
-- -   @INTERNAL_FAILURE@
--
-- -   @INVALID_CHANGE_BATCH@
--
-- -   @THROTTLED_REQUEST@
operation_errorCode :: Lens.Lens' Operation (Prelude.Maybe Prelude.Text)
operation_errorCode :: Lens' Operation (Maybe Text)
operation_errorCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Operation' {Maybe Text
errorCode :: Maybe Text
$sel:errorCode:Operation' :: Operation -> Maybe Text
errorCode} -> Maybe Text
errorCode) (\s :: Operation
s@Operation' {} Maybe Text
a -> Operation
s {$sel:errorCode:Operation' :: Maybe Text
errorCode = Maybe Text
a} :: Operation)

-- | If the value of @Status@ is @FAIL@, the reason that the operation
-- failed.
operation_errorMessage :: Lens.Lens' Operation (Prelude.Maybe Prelude.Text)
operation_errorMessage :: Lens' Operation (Maybe Text)
operation_errorMessage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Operation' {Maybe Text
errorMessage :: Maybe Text
$sel:errorMessage:Operation' :: Operation -> Maybe Text
errorMessage} -> Maybe Text
errorMessage) (\s :: Operation
s@Operation' {} Maybe Text
a -> Operation
s {$sel:errorMessage:Operation' :: Maybe Text
errorMessage = Maybe Text
a} :: Operation)

-- | The ID of the operation that you want to get information about.
operation_id :: Lens.Lens' Operation (Prelude.Maybe Prelude.Text)
operation_id :: Lens' Operation (Maybe Text)
operation_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Operation' {Maybe Text
id :: Maybe Text
$sel:id:Operation' :: Operation -> Maybe Text
id} -> Maybe Text
id) (\s :: Operation
s@Operation' {} Maybe Text
a -> Operation
s {$sel:id:Operation' :: Maybe Text
id = Maybe Text
a} :: Operation)

-- | The status of the operation. Values include the following:
--
-- [SUBMITTED]
--     This is the initial state that occurs immediately after you submit a
--     request.
--
-- [PENDING]
--     Cloud Map is performing the operation.
--
-- [SUCCESS]
--     The operation succeeded.
--
-- [FAIL]
--     The operation failed. For the failure reason, see @ErrorMessage@.
operation_status :: Lens.Lens' Operation (Prelude.Maybe OperationStatus)
operation_status :: Lens' Operation (Maybe OperationStatus)
operation_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Operation' {Maybe OperationStatus
status :: Maybe OperationStatus
$sel:status:Operation' :: Operation -> Maybe OperationStatus
status} -> Maybe OperationStatus
status) (\s :: Operation
s@Operation' {} Maybe OperationStatus
a -> Operation
s {$sel:status:Operation' :: Maybe OperationStatus
status = Maybe OperationStatus
a} :: Operation)

-- | The name of the target entity that\'s associated with the operation:
--
-- [NAMESPACE]
--     The namespace ID is returned in the @ResourceId@ property.
--
-- [SERVICE]
--     The service ID is returned in the @ResourceId@ property.
--
-- [INSTANCE]
--     The instance ID is returned in the @ResourceId@ property.
operation_targets :: Lens.Lens' Operation (Prelude.Maybe (Prelude.HashMap OperationTargetType Prelude.Text))
operation_targets :: Lens' Operation (Maybe (HashMap OperationTargetType Text))
operation_targets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Operation' {Maybe (HashMap OperationTargetType Text)
targets :: Maybe (HashMap OperationTargetType Text)
$sel:targets:Operation' :: Operation -> Maybe (HashMap OperationTargetType Text)
targets} -> Maybe (HashMap OperationTargetType Text)
targets) (\s :: Operation
s@Operation' {} Maybe (HashMap OperationTargetType Text)
a -> Operation
s {$sel:targets:Operation' :: Maybe (HashMap OperationTargetType Text)
targets = Maybe (HashMap OperationTargetType Text)
a} :: Operation) 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 name of the operation that\'s associated with the specified ID.
operation_type :: Lens.Lens' Operation (Prelude.Maybe OperationType)
operation_type :: Lens' Operation (Maybe OperationType)
operation_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Operation' {Maybe OperationType
type' :: Maybe OperationType
$sel:type':Operation' :: Operation -> Maybe OperationType
type'} -> Maybe OperationType
type') (\s :: Operation
s@Operation' {} Maybe OperationType
a -> Operation
s {$sel:type':Operation' :: Maybe OperationType
type' = Maybe OperationType
a} :: Operation)

-- | The date and time that the value of @Status@ changed to the current
-- value, in Unix date\/time format and Coordinated Universal Time (UTC).
-- The value of @UpdateDate@ is accurate to milliseconds. For example, the
-- value @1516925490.087@ represents Friday, January 26, 2018 12:11:30.087
-- AM.
operation_updateDate :: Lens.Lens' Operation (Prelude.Maybe Prelude.UTCTime)
operation_updateDate :: Lens' Operation (Maybe UTCTime)
operation_updateDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Operation' {Maybe POSIX
updateDate :: Maybe POSIX
$sel:updateDate:Operation' :: Operation -> Maybe POSIX
updateDate} -> Maybe POSIX
updateDate) (\s :: Operation
s@Operation' {} Maybe POSIX
a -> Operation
s {$sel:updateDate:Operation' :: Maybe POSIX
updateDate = Maybe POSIX
a} :: Operation) 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

instance Data.FromJSON Operation where
  parseJSON :: Value -> Parser Operation
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Operation"
      ( \Object
x ->
          Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe OperationStatus
-> Maybe (HashMap OperationTargetType Text)
-> Maybe OperationType
-> Maybe POSIX
-> Operation
Operation'
            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
"CreateDate")
            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
"ErrorCode")
            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
"ErrorMessage")
            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
"Id")
            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
"Targets" 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
"Type")
            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
"UpdateDate")
      )

instance Prelude.Hashable Operation where
  hashWithSalt :: Int -> Operation -> Int
hashWithSalt Int
_salt Operation' {Maybe Text
Maybe (HashMap OperationTargetType Text)
Maybe POSIX
Maybe OperationStatus
Maybe OperationType
updateDate :: Maybe POSIX
type' :: Maybe OperationType
targets :: Maybe (HashMap OperationTargetType Text)
status :: Maybe OperationStatus
id :: Maybe Text
errorMessage :: Maybe Text
errorCode :: Maybe Text
createDate :: Maybe POSIX
$sel:updateDate:Operation' :: Operation -> Maybe POSIX
$sel:type':Operation' :: Operation -> Maybe OperationType
$sel:targets:Operation' :: Operation -> Maybe (HashMap OperationTargetType Text)
$sel:status:Operation' :: Operation -> Maybe OperationStatus
$sel:id:Operation' :: Operation -> Maybe Text
$sel:errorMessage:Operation' :: Operation -> Maybe Text
$sel:errorCode:Operation' :: Operation -> Maybe Text
$sel:createDate:Operation' :: Operation -> Maybe POSIX
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createDate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
errorCode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
errorMessage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe OperationStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap OperationTargetType Text)
targets
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe OperationType
type'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
updateDate

instance Prelude.NFData Operation where
  rnf :: Operation -> ()
rnf Operation' {Maybe Text
Maybe (HashMap OperationTargetType Text)
Maybe POSIX
Maybe OperationStatus
Maybe OperationType
updateDate :: Maybe POSIX
type' :: Maybe OperationType
targets :: Maybe (HashMap OperationTargetType Text)
status :: Maybe OperationStatus
id :: Maybe Text
errorMessage :: Maybe Text
errorCode :: Maybe Text
createDate :: Maybe POSIX
$sel:updateDate:Operation' :: Operation -> Maybe POSIX
$sel:type':Operation' :: Operation -> Maybe OperationType
$sel:targets:Operation' :: Operation -> Maybe (HashMap OperationTargetType Text)
$sel:status:Operation' :: Operation -> Maybe OperationStatus
$sel:id:Operation' :: Operation -> Maybe Text
$sel:errorMessage:Operation' :: Operation -> Maybe Text
$sel:errorCode:Operation' :: Operation -> Maybe Text
$sel:createDate:Operation' :: Operation -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
errorCode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
errorMessage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OperationStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap OperationTargetType Text)
targets
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OperationType
type'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
updateDate