{-# 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.CancelSimulationJobBatch
-- 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 a simulation job batch. When you cancel a simulation job batch,
-- you are also cancelling all of the active simulation jobs created as
-- part of the batch.
module Amazonka.RobOMaker.CancelSimulationJobBatch
  ( -- * Creating a Request
    CancelSimulationJobBatch (..),
    newCancelSimulationJobBatch,

    -- * Request Lenses
    cancelSimulationJobBatch_batch,

    -- * Destructuring the Response
    CancelSimulationJobBatchResponse (..),
    newCancelSimulationJobBatchResponse,

    -- * Response Lenses
    cancelSimulationJobBatchResponse_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:/ 'newCancelSimulationJobBatch' smart constructor.
data CancelSimulationJobBatch = CancelSimulationJobBatch'
  { -- | The id of the batch to cancel.
    CancelSimulationJobBatch -> Text
batch :: Prelude.Text
  }
  deriving (CancelSimulationJobBatch -> CancelSimulationJobBatch -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CancelSimulationJobBatch -> CancelSimulationJobBatch -> Bool
$c/= :: CancelSimulationJobBatch -> CancelSimulationJobBatch -> Bool
== :: CancelSimulationJobBatch -> CancelSimulationJobBatch -> Bool
$c== :: CancelSimulationJobBatch -> CancelSimulationJobBatch -> Bool
Prelude.Eq, ReadPrec [CancelSimulationJobBatch]
ReadPrec CancelSimulationJobBatch
Int -> ReadS CancelSimulationJobBatch
ReadS [CancelSimulationJobBatch]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CancelSimulationJobBatch]
$creadListPrec :: ReadPrec [CancelSimulationJobBatch]
readPrec :: ReadPrec CancelSimulationJobBatch
$creadPrec :: ReadPrec CancelSimulationJobBatch
readList :: ReadS [CancelSimulationJobBatch]
$creadList :: ReadS [CancelSimulationJobBatch]
readsPrec :: Int -> ReadS CancelSimulationJobBatch
$creadsPrec :: Int -> ReadS CancelSimulationJobBatch
Prelude.Read, Int -> CancelSimulationJobBatch -> ShowS
[CancelSimulationJobBatch] -> ShowS
CancelSimulationJobBatch -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CancelSimulationJobBatch] -> ShowS
$cshowList :: [CancelSimulationJobBatch] -> ShowS
show :: CancelSimulationJobBatch -> String
$cshow :: CancelSimulationJobBatch -> String
showsPrec :: Int -> CancelSimulationJobBatch -> ShowS
$cshowsPrec :: Int -> CancelSimulationJobBatch -> ShowS
Prelude.Show, forall x.
Rep CancelSimulationJobBatch x -> CancelSimulationJobBatch
forall x.
CancelSimulationJobBatch -> Rep CancelSimulationJobBatch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CancelSimulationJobBatch x -> CancelSimulationJobBatch
$cfrom :: forall x.
CancelSimulationJobBatch -> Rep CancelSimulationJobBatch x
Prelude.Generic)

-- |
-- Create a value of 'CancelSimulationJobBatch' 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:
--
-- 'batch', 'cancelSimulationJobBatch_batch' - The id of the batch to cancel.
newCancelSimulationJobBatch ::
  -- | 'batch'
  Prelude.Text ->
  CancelSimulationJobBatch
newCancelSimulationJobBatch :: Text -> CancelSimulationJobBatch
newCancelSimulationJobBatch Text
pBatch_ =
  CancelSimulationJobBatch' {$sel:batch:CancelSimulationJobBatch' :: Text
batch = Text
pBatch_}

-- | The id of the batch to cancel.
cancelSimulationJobBatch_batch :: Lens.Lens' CancelSimulationJobBatch Prelude.Text
cancelSimulationJobBatch_batch :: Lens' CancelSimulationJobBatch Text
cancelSimulationJobBatch_batch = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelSimulationJobBatch' {Text
batch :: Text
$sel:batch:CancelSimulationJobBatch' :: CancelSimulationJobBatch -> Text
batch} -> Text
batch) (\s :: CancelSimulationJobBatch
s@CancelSimulationJobBatch' {} Text
a -> CancelSimulationJobBatch
s {$sel:batch:CancelSimulationJobBatch' :: Text
batch = Text
a} :: CancelSimulationJobBatch)

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

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

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

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

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

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

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

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

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