{-# 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.Forecast.StopResource
-- 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 a resource.
--
-- The resource undergoes the following states: @CREATE_STOPPING@ and
-- @CREATE_STOPPED@. You cannot resume a resource once it has been stopped.
--
-- This operation can be applied to the following resources (and their
-- corresponding child resources):
--
-- -   Dataset Import Job
--
-- -   Predictor Job
--
-- -   Forecast Job
--
-- -   Forecast Export Job
--
-- -   Predictor Backtest Export Job
--
-- -   Explainability Job
--
-- -   Explainability Export Job
module Amazonka.Forecast.StopResource
  ( -- * Creating a Request
    StopResource (..),
    newStopResource,

    -- * Request Lenses
    stopResource_resourceArn,

    -- * Destructuring the Response
    StopResourceResponse (..),
    newStopResourceResponse,
  )
where

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

-- | /See:/ 'newStopResource' smart constructor.
data StopResource = StopResource'
  { -- | The Amazon Resource Name (ARN) that identifies the resource to stop. The
    -- supported ARNs are @DatasetImportJobArn@, @PredictorArn@,
    -- @PredictorBacktestExportJobArn@, @ForecastArn@, @ForecastExportJobArn@,
    -- @ExplainabilityArn@, and @ExplainabilityExportArn@.
    StopResource -> Text
resourceArn :: Prelude.Text
  }
  deriving (StopResource -> StopResource -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopResource -> StopResource -> Bool
$c/= :: StopResource -> StopResource -> Bool
== :: StopResource -> StopResource -> Bool
$c== :: StopResource -> StopResource -> Bool
Prelude.Eq, ReadPrec [StopResource]
ReadPrec StopResource
Int -> ReadS StopResource
ReadS [StopResource]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopResource]
$creadListPrec :: ReadPrec [StopResource]
readPrec :: ReadPrec StopResource
$creadPrec :: ReadPrec StopResource
readList :: ReadS [StopResource]
$creadList :: ReadS [StopResource]
readsPrec :: Int -> ReadS StopResource
$creadsPrec :: Int -> ReadS StopResource
Prelude.Read, Int -> StopResource -> ShowS
[StopResource] -> ShowS
StopResource -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopResource] -> ShowS
$cshowList :: [StopResource] -> ShowS
show :: StopResource -> String
$cshow :: StopResource -> String
showsPrec :: Int -> StopResource -> ShowS
$cshowsPrec :: Int -> StopResource -> ShowS
Prelude.Show, forall x. Rep StopResource x -> StopResource
forall x. StopResource -> Rep StopResource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StopResource x -> StopResource
$cfrom :: forall x. StopResource -> Rep StopResource x
Prelude.Generic)

-- |
-- Create a value of 'StopResource' 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:
--
-- 'resourceArn', 'stopResource_resourceArn' - The Amazon Resource Name (ARN) that identifies the resource to stop. The
-- supported ARNs are @DatasetImportJobArn@, @PredictorArn@,
-- @PredictorBacktestExportJobArn@, @ForecastArn@, @ForecastExportJobArn@,
-- @ExplainabilityArn@, and @ExplainabilityExportArn@.
newStopResource ::
  -- | 'resourceArn'
  Prelude.Text ->
  StopResource
newStopResource :: Text -> StopResource
newStopResource Text
pResourceArn_ =
  StopResource' {$sel:resourceArn:StopResource' :: Text
resourceArn = Text
pResourceArn_}

-- | The Amazon Resource Name (ARN) that identifies the resource to stop. The
-- supported ARNs are @DatasetImportJobArn@, @PredictorArn@,
-- @PredictorBacktestExportJobArn@, @ForecastArn@, @ForecastExportJobArn@,
-- @ExplainabilityArn@, and @ExplainabilityExportArn@.
stopResource_resourceArn :: Lens.Lens' StopResource Prelude.Text
stopResource_resourceArn :: Lens' StopResource Text
stopResource_resourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopResource' {Text
resourceArn :: Text
$sel:resourceArn:StopResource' :: StopResource -> Text
resourceArn} -> Text
resourceArn) (\s :: StopResource
s@StopResource' {} Text
a -> StopResource
s {$sel:resourceArn:StopResource' :: Text
resourceArn = Text
a} :: StopResource)

instance Core.AWSRequest StopResource where
  type AWSResponse StopResource = StopResourceResponse
  request :: (Service -> Service) -> StopResource -> Request StopResource
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 StopResource
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse StopResource)))
response = forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull StopResourceResponse
StopResourceResponse'

instance Prelude.Hashable StopResource where
  hashWithSalt :: Int -> StopResource -> Int
hashWithSalt Int
_salt StopResource' {Text
resourceArn :: Text
$sel:resourceArn:StopResource' :: StopResource -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceArn

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

instance Data.ToHeaders StopResource where
  toHeaders :: StopResource -> [Header]
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 -> [Header]
Data.=# ( ByteString
"AmazonForecast.StopResource" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

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

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

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

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

-- |
-- Create a value of 'StopResourceResponse' 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.
newStopResourceResponse ::
  StopResourceResponse
newStopResourceResponse :: StopResourceResponse
newStopResourceResponse = StopResourceResponse
StopResourceResponse'

instance Prelude.NFData StopResourceResponse where
  rnf :: StopResourceResponse -> ()
rnf StopResourceResponse
_ = ()