{-# 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.DeleteWhatIfForecast
-- 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 what-if forecast created using the CreateWhatIfForecast
-- operation. You can delete only what-if forecasts that have a status of
-- @ACTIVE@ or @CREATE_FAILED@. To get the status, use the
-- DescribeWhatIfForecast operation.
--
-- You can\'t delete a what-if forecast while it is being exported. After a
-- what-if forecast is deleted, you can no longer query the what-if
-- analysis.
module Amazonka.Forecast.DeleteWhatIfForecast
  ( -- * Creating a Request
    DeleteWhatIfForecast (..),
    newDeleteWhatIfForecast,

    -- * Request Lenses
    deleteWhatIfForecast_whatIfForecastArn,

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

-- |
-- Create a value of 'DeleteWhatIfForecast' 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:
--
-- 'whatIfForecastArn', 'deleteWhatIfForecast_whatIfForecastArn' - The Amazon Resource Name (ARN) of the what-if forecast that you want to
-- delete.
newDeleteWhatIfForecast ::
  -- | 'whatIfForecastArn'
  Prelude.Text ->
  DeleteWhatIfForecast
newDeleteWhatIfForecast :: Text -> DeleteWhatIfForecast
newDeleteWhatIfForecast Text
pWhatIfForecastArn_ =
  DeleteWhatIfForecast'
    { $sel:whatIfForecastArn:DeleteWhatIfForecast' :: Text
whatIfForecastArn =
        Text
pWhatIfForecastArn_
    }

-- | The Amazon Resource Name (ARN) of the what-if forecast that you want to
-- delete.
deleteWhatIfForecast_whatIfForecastArn :: Lens.Lens' DeleteWhatIfForecast Prelude.Text
deleteWhatIfForecast_whatIfForecastArn :: Lens' DeleteWhatIfForecast Text
deleteWhatIfForecast_whatIfForecastArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteWhatIfForecast' {Text
whatIfForecastArn :: Text
$sel:whatIfForecastArn:DeleteWhatIfForecast' :: DeleteWhatIfForecast -> Text
whatIfForecastArn} -> Text
whatIfForecastArn) (\s :: DeleteWhatIfForecast
s@DeleteWhatIfForecast' {} Text
a -> DeleteWhatIfForecast
s {$sel:whatIfForecastArn:DeleteWhatIfForecast' :: Text
whatIfForecastArn = Text
a} :: DeleteWhatIfForecast)

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

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

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

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

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

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

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

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

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