{-# 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.Personalize.DeleteSolution
-- 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 all versions of a solution and the @Solution@ object itself.
-- Before deleting a solution, you must delete all campaigns based on the
-- solution. To determine what campaigns are using the solution, call
-- <https://docs.aws.amazon.com/personalize/latest/dg/API_ListCampaigns.html ListCampaigns>
-- and supply the Amazon Resource Name (ARN) of the solution. You can\'t
-- delete a solution if an associated @SolutionVersion@ is in the CREATE
-- PENDING or IN PROGRESS state. For more information on solutions, see
-- <https://docs.aws.amazon.com/personalize/latest/dg/API_CreateSolution.html CreateSolution>.
module Amazonka.Personalize.DeleteSolution
  ( -- * Creating a Request
    DeleteSolution (..),
    newDeleteSolution,

    -- * Request Lenses
    deleteSolution_solutionArn,

    -- * Destructuring the Response
    DeleteSolutionResponse (..),
    newDeleteSolutionResponse,
  )
where

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

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

-- |
-- Create a value of 'DeleteSolution' 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:
--
-- 'solutionArn', 'deleteSolution_solutionArn' - The ARN of the solution to delete.
newDeleteSolution ::
  -- | 'solutionArn'
  Prelude.Text ->
  DeleteSolution
newDeleteSolution :: Text -> DeleteSolution
newDeleteSolution Text
pSolutionArn_ =
  DeleteSolution' {$sel:solutionArn:DeleteSolution' :: Text
solutionArn = Text
pSolutionArn_}

-- | The ARN of the solution to delete.
deleteSolution_solutionArn :: Lens.Lens' DeleteSolution Prelude.Text
deleteSolution_solutionArn :: Lens' DeleteSolution Text
deleteSolution_solutionArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteSolution' {Text
solutionArn :: Text
$sel:solutionArn:DeleteSolution' :: DeleteSolution -> Text
solutionArn} -> Text
solutionArn) (\s :: DeleteSolution
s@DeleteSolution' {} Text
a -> DeleteSolution
s {$sel:solutionArn:DeleteSolution' :: Text
solutionArn = Text
a} :: DeleteSolution)

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

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

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

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

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

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

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

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

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