{-# 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.RobOMaker.CancelWorldExportJob
-- 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 the specified export job.
module Amazonka.RobOMaker.CancelWorldExportJob
  ( -- * Creating a Request
    CancelWorldExportJob (..),
    newCancelWorldExportJob,

    -- * Request Lenses
    cancelWorldExportJob_job,

    -- * Destructuring the Response
    CancelWorldExportJobResponse (..),
    newCancelWorldExportJobResponse,

    -- * Response Lenses
    cancelWorldExportJobResponse_httpStatus,
  )
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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.RobOMaker.Types

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

-- |
-- Create a value of 'CancelWorldExportJob' 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:
--
-- 'job', 'cancelWorldExportJob_job' - The Amazon Resource Name (arn) of the world export job to cancel.
newCancelWorldExportJob ::
  -- | 'job'
  Prelude.Text ->
  CancelWorldExportJob
newCancelWorldExportJob :: Text -> CancelWorldExportJob
newCancelWorldExportJob Text
pJob_ =
  CancelWorldExportJob' {$sel:job:CancelWorldExportJob' :: Text
job = Text
pJob_}

-- | The Amazon Resource Name (arn) of the world export job to cancel.
cancelWorldExportJob_job :: Lens.Lens' CancelWorldExportJob Prelude.Text
cancelWorldExportJob_job :: Lens' CancelWorldExportJob Text
cancelWorldExportJob_job = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelWorldExportJob' {Text
job :: Text
$sel:job:CancelWorldExportJob' :: CancelWorldExportJob -> Text
job} -> Text
job) (\s :: CancelWorldExportJob
s@CancelWorldExportJob' {} Text
a -> CancelWorldExportJob
s {$sel:job:CancelWorldExportJob' :: Text
job = Text
a} :: CancelWorldExportJob)

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

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

instance Data.ToHeaders CancelWorldExportJob where
  toHeaders :: CancelWorldExportJob -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON CancelWorldExportJob where
  toJSON :: CancelWorldExportJob -> Value
toJSON CancelWorldExportJob' {Text
job :: Text
$sel:job:CancelWorldExportJob' :: CancelWorldExportJob -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"job" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
job)]
      )

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

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

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

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

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

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