{-# 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.DMS.StartReplicationTaskAssessment
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Starts the replication task assessment for unsupported data types in the
-- source database.
--
-- You can only use this operation for a task if the following conditions
-- are true:
--
-- -   The task must be in the @stopped@ state.
--
-- -   The task must have successful connections to the source and target.
--
-- If either of these conditions are not met, an
-- @InvalidResourceStateFault@ error will result.
--
-- For information about DMS task assessments, see
-- <https://docs.aws.amazon.com/dms/latest/userguide/CHAP_Tasks.AssessmentReport.html Creating a task assessment report>
-- in the /Database Migration Service User Guide/.
module Amazonka.DMS.StartReplicationTaskAssessment
  ( -- * Creating a Request
    StartReplicationTaskAssessment (..),
    newStartReplicationTaskAssessment,

    -- * Request Lenses
    startReplicationTaskAssessment_replicationTaskArn,

    -- * Destructuring the Response
    StartReplicationTaskAssessmentResponse (..),
    newStartReplicationTaskAssessmentResponse,

    -- * Response Lenses
    startReplicationTaskAssessmentResponse_replicationTask,
    startReplicationTaskAssessmentResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import Amazonka.DMS.Types
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- |
--
-- /See:/ 'newStartReplicationTaskAssessment' smart constructor.
data StartReplicationTaskAssessment = StartReplicationTaskAssessment'
  { -- | The Amazon Resource Name (ARN) of the replication task.
    StartReplicationTaskAssessment -> Text
replicationTaskArn :: Prelude.Text
  }
  deriving (StartReplicationTaskAssessment
-> StartReplicationTaskAssessment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartReplicationTaskAssessment
-> StartReplicationTaskAssessment -> Bool
$c/= :: StartReplicationTaskAssessment
-> StartReplicationTaskAssessment -> Bool
== :: StartReplicationTaskAssessment
-> StartReplicationTaskAssessment -> Bool
$c== :: StartReplicationTaskAssessment
-> StartReplicationTaskAssessment -> Bool
Prelude.Eq, ReadPrec [StartReplicationTaskAssessment]
ReadPrec StartReplicationTaskAssessment
Int -> ReadS StartReplicationTaskAssessment
ReadS [StartReplicationTaskAssessment]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartReplicationTaskAssessment]
$creadListPrec :: ReadPrec [StartReplicationTaskAssessment]
readPrec :: ReadPrec StartReplicationTaskAssessment
$creadPrec :: ReadPrec StartReplicationTaskAssessment
readList :: ReadS [StartReplicationTaskAssessment]
$creadList :: ReadS [StartReplicationTaskAssessment]
readsPrec :: Int -> ReadS StartReplicationTaskAssessment
$creadsPrec :: Int -> ReadS StartReplicationTaskAssessment
Prelude.Read, Int -> StartReplicationTaskAssessment -> ShowS
[StartReplicationTaskAssessment] -> ShowS
StartReplicationTaskAssessment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartReplicationTaskAssessment] -> ShowS
$cshowList :: [StartReplicationTaskAssessment] -> ShowS
show :: StartReplicationTaskAssessment -> String
$cshow :: StartReplicationTaskAssessment -> String
showsPrec :: Int -> StartReplicationTaskAssessment -> ShowS
$cshowsPrec :: Int -> StartReplicationTaskAssessment -> ShowS
Prelude.Show, forall x.
Rep StartReplicationTaskAssessment x
-> StartReplicationTaskAssessment
forall x.
StartReplicationTaskAssessment
-> Rep StartReplicationTaskAssessment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StartReplicationTaskAssessment x
-> StartReplicationTaskAssessment
$cfrom :: forall x.
StartReplicationTaskAssessment
-> Rep StartReplicationTaskAssessment x
Prelude.Generic)

-- |
-- Create a value of 'StartReplicationTaskAssessment' 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:
--
-- 'replicationTaskArn', 'startReplicationTaskAssessment_replicationTaskArn' - The Amazon Resource Name (ARN) of the replication task.
newStartReplicationTaskAssessment ::
  -- | 'replicationTaskArn'
  Prelude.Text ->
  StartReplicationTaskAssessment
newStartReplicationTaskAssessment :: Text -> StartReplicationTaskAssessment
newStartReplicationTaskAssessment
  Text
pReplicationTaskArn_ =
    StartReplicationTaskAssessment'
      { $sel:replicationTaskArn:StartReplicationTaskAssessment' :: Text
replicationTaskArn =
          Text
pReplicationTaskArn_
      }

-- | The Amazon Resource Name (ARN) of the replication task.
startReplicationTaskAssessment_replicationTaskArn :: Lens.Lens' StartReplicationTaskAssessment Prelude.Text
startReplicationTaskAssessment_replicationTaskArn :: Lens' StartReplicationTaskAssessment Text
startReplicationTaskAssessment_replicationTaskArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartReplicationTaskAssessment' {Text
replicationTaskArn :: Text
$sel:replicationTaskArn:StartReplicationTaskAssessment' :: StartReplicationTaskAssessment -> Text
replicationTaskArn} -> Text
replicationTaskArn) (\s :: StartReplicationTaskAssessment
s@StartReplicationTaskAssessment' {} Text
a -> StartReplicationTaskAssessment
s {$sel:replicationTaskArn:StartReplicationTaskAssessment' :: Text
replicationTaskArn = Text
a} :: StartReplicationTaskAssessment)

instance
  Core.AWSRequest
    StartReplicationTaskAssessment
  where
  type
    AWSResponse StartReplicationTaskAssessment =
      StartReplicationTaskAssessmentResponse
  request :: (Service -> Service)
-> StartReplicationTaskAssessment
-> Request StartReplicationTaskAssessment
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 StartReplicationTaskAssessment
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse StartReplicationTaskAssessment)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe ReplicationTask
-> Int -> StartReplicationTaskAssessmentResponse
StartReplicationTaskAssessmentResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ReplicationTask")
            forall (f :: * -> *) a b. Applicative f => 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
    StartReplicationTaskAssessment
  where
  hashWithSalt :: Int -> StartReplicationTaskAssessment -> Int
hashWithSalt
    Int
_salt
    StartReplicationTaskAssessment' {Text
replicationTaskArn :: Text
$sel:replicationTaskArn:StartReplicationTaskAssessment' :: StartReplicationTaskAssessment -> Text
..} =
      Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
replicationTaskArn

instance
  Prelude.NFData
    StartReplicationTaskAssessment
  where
  rnf :: StartReplicationTaskAssessment -> ()
rnf StartReplicationTaskAssessment' {Text
replicationTaskArn :: Text
$sel:replicationTaskArn:StartReplicationTaskAssessment' :: StartReplicationTaskAssessment -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
replicationTaskArn

instance
  Data.ToHeaders
    StartReplicationTaskAssessment
  where
  toHeaders :: StartReplicationTaskAssessment -> 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
"AmazonDMSv20160101.StartReplicationTaskAssessment" ::
                          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 StartReplicationTaskAssessment where
  toJSON :: StartReplicationTaskAssessment -> Value
toJSON StartReplicationTaskAssessment' {Text
replicationTaskArn :: Text
$sel:replicationTaskArn:StartReplicationTaskAssessment' :: StartReplicationTaskAssessment -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"ReplicationTaskArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
replicationTaskArn)
          ]
      )

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

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

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

-- |
-- Create a value of 'StartReplicationTaskAssessmentResponse' 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:
--
-- 'replicationTask', 'startReplicationTaskAssessmentResponse_replicationTask' - The assessed replication task.
--
-- 'httpStatus', 'startReplicationTaskAssessmentResponse_httpStatus' - The response's http status code.
newStartReplicationTaskAssessmentResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StartReplicationTaskAssessmentResponse
newStartReplicationTaskAssessmentResponse :: Int -> StartReplicationTaskAssessmentResponse
newStartReplicationTaskAssessmentResponse
  Int
pHttpStatus_ =
    StartReplicationTaskAssessmentResponse'
      { $sel:replicationTask:StartReplicationTaskAssessmentResponse' :: Maybe ReplicationTask
replicationTask =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:StartReplicationTaskAssessmentResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | The assessed replication task.
startReplicationTaskAssessmentResponse_replicationTask :: Lens.Lens' StartReplicationTaskAssessmentResponse (Prelude.Maybe ReplicationTask)
startReplicationTaskAssessmentResponse_replicationTask :: Lens'
  StartReplicationTaskAssessmentResponse (Maybe ReplicationTask)
startReplicationTaskAssessmentResponse_replicationTask = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartReplicationTaskAssessmentResponse' {Maybe ReplicationTask
replicationTask :: Maybe ReplicationTask
$sel:replicationTask:StartReplicationTaskAssessmentResponse' :: StartReplicationTaskAssessmentResponse -> Maybe ReplicationTask
replicationTask} -> Maybe ReplicationTask
replicationTask) (\s :: StartReplicationTaskAssessmentResponse
s@StartReplicationTaskAssessmentResponse' {} Maybe ReplicationTask
a -> StartReplicationTaskAssessmentResponse
s {$sel:replicationTask:StartReplicationTaskAssessmentResponse' :: Maybe ReplicationTask
replicationTask = Maybe ReplicationTask
a} :: StartReplicationTaskAssessmentResponse)

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

instance
  Prelude.NFData
    StartReplicationTaskAssessmentResponse
  where
  rnf :: StartReplicationTaskAssessmentResponse -> ()
rnf StartReplicationTaskAssessmentResponse' {Int
Maybe ReplicationTask
httpStatus :: Int
replicationTask :: Maybe ReplicationTask
$sel:httpStatus:StartReplicationTaskAssessmentResponse' :: StartReplicationTaskAssessmentResponse -> Int
$sel:replicationTask:StartReplicationTaskAssessmentResponse' :: StartReplicationTaskAssessmentResponse -> Maybe ReplicationTask
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ReplicationTask
replicationTask
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus