{-# 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.FraudDetector.CancelBatchImportJob
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Cancels an in-progress batch import job.
module Amazonka.FraudDetector.CancelBatchImportJob
  ( -- * Creating a Request
    CancelBatchImportJob (..),
    newCancelBatchImportJob,

    -- * Request Lenses
    cancelBatchImportJob_jobId,

    -- * Destructuring the Response
    CancelBatchImportJobResponse (..),
    newCancelBatchImportJobResponse,

    -- * Response Lenses
    cancelBatchImportJobResponse_httpStatus,
  )
where

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

-- | /See:/ 'newCancelBatchImportJob' smart constructor.
data CancelBatchImportJob = CancelBatchImportJob'
  { -- | The ID of an in-progress batch import job to cancel.
    --
    -- Amazon Fraud Detector will throw an error if the batch import job is in
    -- @FAILED@, @CANCELED@, or @COMPLETED@ state.
    CancelBatchImportJob -> Text
jobId :: Prelude.Text
  }
  deriving (CancelBatchImportJob -> CancelBatchImportJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CancelBatchImportJob -> CancelBatchImportJob -> Bool
$c/= :: CancelBatchImportJob -> CancelBatchImportJob -> Bool
== :: CancelBatchImportJob -> CancelBatchImportJob -> Bool
$c== :: CancelBatchImportJob -> CancelBatchImportJob -> Bool
Prelude.Eq, ReadPrec [CancelBatchImportJob]
ReadPrec CancelBatchImportJob
Int -> ReadS CancelBatchImportJob
ReadS [CancelBatchImportJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CancelBatchImportJob]
$creadListPrec :: ReadPrec [CancelBatchImportJob]
readPrec :: ReadPrec CancelBatchImportJob
$creadPrec :: ReadPrec CancelBatchImportJob
readList :: ReadS [CancelBatchImportJob]
$creadList :: ReadS [CancelBatchImportJob]
readsPrec :: Int -> ReadS CancelBatchImportJob
$creadsPrec :: Int -> ReadS CancelBatchImportJob
Prelude.Read, Int -> CancelBatchImportJob -> ShowS
[CancelBatchImportJob] -> ShowS
CancelBatchImportJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CancelBatchImportJob] -> ShowS
$cshowList :: [CancelBatchImportJob] -> ShowS
show :: CancelBatchImportJob -> String
$cshow :: CancelBatchImportJob -> String
showsPrec :: Int -> CancelBatchImportJob -> ShowS
$cshowsPrec :: Int -> CancelBatchImportJob -> ShowS
Prelude.Show, forall x. Rep CancelBatchImportJob x -> CancelBatchImportJob
forall x. CancelBatchImportJob -> Rep CancelBatchImportJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CancelBatchImportJob x -> CancelBatchImportJob
$cfrom :: forall x. CancelBatchImportJob -> Rep CancelBatchImportJob x
Prelude.Generic)

-- |
-- Create a value of 'CancelBatchImportJob' 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:
--
-- 'jobId', 'cancelBatchImportJob_jobId' - The ID of an in-progress batch import job to cancel.
--
-- Amazon Fraud Detector will throw an error if the batch import job is in
-- @FAILED@, @CANCELED@, or @COMPLETED@ state.
newCancelBatchImportJob ::
  -- | 'jobId'
  Prelude.Text ->
  CancelBatchImportJob
newCancelBatchImportJob :: Text -> CancelBatchImportJob
newCancelBatchImportJob Text
pJobId_ =
  CancelBatchImportJob' {$sel:jobId:CancelBatchImportJob' :: Text
jobId = Text
pJobId_}

-- | The ID of an in-progress batch import job to cancel.
--
-- Amazon Fraud Detector will throw an error if the batch import job is in
-- @FAILED@, @CANCELED@, or @COMPLETED@ state.
cancelBatchImportJob_jobId :: Lens.Lens' CancelBatchImportJob Prelude.Text
cancelBatchImportJob_jobId :: Lens' CancelBatchImportJob Text
cancelBatchImportJob_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelBatchImportJob' {Text
jobId :: Text
$sel:jobId:CancelBatchImportJob' :: CancelBatchImportJob -> Text
jobId} -> Text
jobId) (\s :: CancelBatchImportJob
s@CancelBatchImportJob' {} Text
a -> CancelBatchImportJob
s {$sel:jobId:CancelBatchImportJob' :: Text
jobId = Text
a} :: CancelBatchImportJob)

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

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

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

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

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

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

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

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

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