{-# 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.DataSync.CancelTaskExecution
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Stops an DataSync task execution that\'s in progress. The transfer of
-- some files are abruptly interrupted. File contents that\'re transferred
-- to the destination might be incomplete or inconsistent with the source
-- files.
--
-- However, if you start a new task execution using the same task and allow
-- it to finish, file content on the destination will be complete and
-- consistent. This applies to other unexpected failures that interrupt a
-- task execution. In all of these cases, DataSync successfully completes
-- the transfer when you start the next task execution.
module Amazonka.DataSync.CancelTaskExecution
  ( -- * Creating a Request
    CancelTaskExecution (..),
    newCancelTaskExecution,

    -- * Request Lenses
    cancelTaskExecution_taskExecutionArn,

    -- * Destructuring the Response
    CancelTaskExecutionResponse (..),
    newCancelTaskExecutionResponse,

    -- * Response Lenses
    cancelTaskExecutionResponse_httpStatus,
  )
where

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

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

-- |
-- Create a value of 'CancelTaskExecution' 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:
--
-- 'taskExecutionArn', 'cancelTaskExecution_taskExecutionArn' - The Amazon Resource Name (ARN) of the task execution to stop.
newCancelTaskExecution ::
  -- | 'taskExecutionArn'
  Prelude.Text ->
  CancelTaskExecution
newCancelTaskExecution :: Text -> CancelTaskExecution
newCancelTaskExecution Text
pTaskExecutionArn_ =
  CancelTaskExecution'
    { $sel:taskExecutionArn:CancelTaskExecution' :: Text
taskExecutionArn =
        Text
pTaskExecutionArn_
    }

-- | The Amazon Resource Name (ARN) of the task execution to stop.
cancelTaskExecution_taskExecutionArn :: Lens.Lens' CancelTaskExecution Prelude.Text
cancelTaskExecution_taskExecutionArn :: Lens' CancelTaskExecution Text
cancelTaskExecution_taskExecutionArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelTaskExecution' {Text
taskExecutionArn :: Text
$sel:taskExecutionArn:CancelTaskExecution' :: CancelTaskExecution -> Text
taskExecutionArn} -> Text
taskExecutionArn) (\s :: CancelTaskExecution
s@CancelTaskExecution' {} Text
a -> CancelTaskExecution
s {$sel:taskExecutionArn:CancelTaskExecution' :: Text
taskExecutionArn = Text
a} :: CancelTaskExecution)

instance Core.AWSRequest CancelTaskExecution where
  type
    AWSResponse CancelTaskExecution =
      CancelTaskExecutionResponse
  request :: (Service -> Service)
-> CancelTaskExecution -> Request CancelTaskExecution
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 CancelTaskExecution
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CancelTaskExecution)))
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 -> CancelTaskExecutionResponse
CancelTaskExecutionResponse'
            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 CancelTaskExecution where
  hashWithSalt :: Int -> CancelTaskExecution -> Int
hashWithSalt Int
_salt CancelTaskExecution' {Text
taskExecutionArn :: Text
$sel:taskExecutionArn:CancelTaskExecution' :: CancelTaskExecution -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
taskExecutionArn

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

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

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

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

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

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

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

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