{-# 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.DeleteForecast
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes a forecast created using the CreateForecast operation. You can
-- delete only forecasts that have a status of @ACTIVE@ or @CREATE_FAILED@.
-- To get the status, use the DescribeForecast operation.
--
-- You can\'t delete a forecast while it is being exported. After a
-- forecast is deleted, you can no longer query the forecast.
module Amazonka.Forecast.DeleteForecast
  ( -- * Creating a Request
    DeleteForecast (..),
    newDeleteForecast,

    -- * Request Lenses
    deleteForecast_forecastArn,

    -- * Destructuring the Response
    DeleteForecastResponse (..),
    newDeleteForecastResponse,
  )
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:/ 'newDeleteForecast' smart constructor.
data DeleteForecast = DeleteForecast'
  { -- | The Amazon Resource Name (ARN) of the forecast to delete.
    DeleteForecast -> Text
forecastArn :: Prelude.Text
  }
  deriving (DeleteForecast -> DeleteForecast -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteForecast -> DeleteForecast -> Bool
$c/= :: DeleteForecast -> DeleteForecast -> Bool
== :: DeleteForecast -> DeleteForecast -> Bool
$c== :: DeleteForecast -> DeleteForecast -> Bool
Prelude.Eq, ReadPrec [DeleteForecast]
ReadPrec DeleteForecast
Int -> ReadS DeleteForecast
ReadS [DeleteForecast]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteForecast]
$creadListPrec :: ReadPrec [DeleteForecast]
readPrec :: ReadPrec DeleteForecast
$creadPrec :: ReadPrec DeleteForecast
readList :: ReadS [DeleteForecast]
$creadList :: ReadS [DeleteForecast]
readsPrec :: Int -> ReadS DeleteForecast
$creadsPrec :: Int -> ReadS DeleteForecast
Prelude.Read, Int -> DeleteForecast -> ShowS
[DeleteForecast] -> ShowS
DeleteForecast -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteForecast] -> ShowS
$cshowList :: [DeleteForecast] -> ShowS
show :: DeleteForecast -> String
$cshow :: DeleteForecast -> String
showsPrec :: Int -> DeleteForecast -> ShowS
$cshowsPrec :: Int -> DeleteForecast -> ShowS
Prelude.Show, forall x. Rep DeleteForecast x -> DeleteForecast
forall x. DeleteForecast -> Rep DeleteForecast x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteForecast x -> DeleteForecast
$cfrom :: forall x. DeleteForecast -> Rep DeleteForecast x
Prelude.Generic)

-- |
-- Create a value of 'DeleteForecast' 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:
--
-- 'forecastArn', 'deleteForecast_forecastArn' - The Amazon Resource Name (ARN) of the forecast to delete.
newDeleteForecast ::
  -- | 'forecastArn'
  Prelude.Text ->
  DeleteForecast
newDeleteForecast :: Text -> DeleteForecast
newDeleteForecast Text
pForecastArn_ =
  DeleteForecast' {$sel:forecastArn:DeleteForecast' :: Text
forecastArn = Text
pForecastArn_}

-- | The Amazon Resource Name (ARN) of the forecast to delete.
deleteForecast_forecastArn :: Lens.Lens' DeleteForecast Prelude.Text
deleteForecast_forecastArn :: Lens' DeleteForecast Text
deleteForecast_forecastArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteForecast' {Text
forecastArn :: Text
$sel:forecastArn:DeleteForecast' :: DeleteForecast -> Text
forecastArn} -> Text
forecastArn) (\s :: DeleteForecast
s@DeleteForecast' {} Text
a -> DeleteForecast
s {$sel:forecastArn:DeleteForecast' :: Text
forecastArn = Text
a} :: DeleteForecast)

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

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

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

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

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

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

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

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

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