{-# 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.CloudSearch.DeleteExpression
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Removes an @Expression@ from the search domain. For more information,
-- see
-- <http://docs.aws.amazon.com/cloudsearch/latest/developerguide/configuring-expressions.html Configuring Expressions>
-- in the /Amazon CloudSearch Developer Guide/.
module Amazonka.CloudSearch.DeleteExpression
  ( -- * Creating a Request
    DeleteExpression (..),
    newDeleteExpression,

    -- * Request Lenses
    deleteExpression_domainName,
    deleteExpression_expressionName,

    -- * Destructuring the Response
    DeleteExpressionResponse (..),
    newDeleteExpressionResponse,

    -- * Response Lenses
    deleteExpressionResponse_httpStatus,
    deleteExpressionResponse_expression,
  )
where

import Amazonka.CloudSearch.Types
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

-- | Container for the parameters to the @DeleteExpression@ operation.
-- Specifies the name of the domain you want to update and the name of the
-- expression you want to delete.
--
-- /See:/ 'newDeleteExpression' smart constructor.
data DeleteExpression = DeleteExpression'
  { DeleteExpression -> Text
domainName :: Prelude.Text,
    -- | The name of the @Expression@ to delete.
    DeleteExpression -> Text
expressionName :: Prelude.Text
  }
  deriving (DeleteExpression -> DeleteExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteExpression -> DeleteExpression -> Bool
$c/= :: DeleteExpression -> DeleteExpression -> Bool
== :: DeleteExpression -> DeleteExpression -> Bool
$c== :: DeleteExpression -> DeleteExpression -> Bool
Prelude.Eq, ReadPrec [DeleteExpression]
ReadPrec DeleteExpression
Int -> ReadS DeleteExpression
ReadS [DeleteExpression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteExpression]
$creadListPrec :: ReadPrec [DeleteExpression]
readPrec :: ReadPrec DeleteExpression
$creadPrec :: ReadPrec DeleteExpression
readList :: ReadS [DeleteExpression]
$creadList :: ReadS [DeleteExpression]
readsPrec :: Int -> ReadS DeleteExpression
$creadsPrec :: Int -> ReadS DeleteExpression
Prelude.Read, Int -> DeleteExpression -> ShowS
[DeleteExpression] -> ShowS
DeleteExpression -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteExpression] -> ShowS
$cshowList :: [DeleteExpression] -> ShowS
show :: DeleteExpression -> String
$cshow :: DeleteExpression -> String
showsPrec :: Int -> DeleteExpression -> ShowS
$cshowsPrec :: Int -> DeleteExpression -> ShowS
Prelude.Show, forall x. Rep DeleteExpression x -> DeleteExpression
forall x. DeleteExpression -> Rep DeleteExpression x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteExpression x -> DeleteExpression
$cfrom :: forall x. DeleteExpression -> Rep DeleteExpression x
Prelude.Generic)

-- |
-- Create a value of 'DeleteExpression' 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:
--
-- 'domainName', 'deleteExpression_domainName' - Undocumented member.
--
-- 'expressionName', 'deleteExpression_expressionName' - The name of the @Expression@ to delete.
newDeleteExpression ::
  -- | 'domainName'
  Prelude.Text ->
  -- | 'expressionName'
  Prelude.Text ->
  DeleteExpression
newDeleteExpression :: Text -> Text -> DeleteExpression
newDeleteExpression Text
pDomainName_ Text
pExpressionName_ =
  DeleteExpression'
    { $sel:domainName:DeleteExpression' :: Text
domainName = Text
pDomainName_,
      $sel:expressionName:DeleteExpression' :: Text
expressionName = Text
pExpressionName_
    }

-- | Undocumented member.
deleteExpression_domainName :: Lens.Lens' DeleteExpression Prelude.Text
deleteExpression_domainName :: Lens' DeleteExpression Text
deleteExpression_domainName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteExpression' {Text
domainName :: Text
$sel:domainName:DeleteExpression' :: DeleteExpression -> Text
domainName} -> Text
domainName) (\s :: DeleteExpression
s@DeleteExpression' {} Text
a -> DeleteExpression
s {$sel:domainName:DeleteExpression' :: Text
domainName = Text
a} :: DeleteExpression)

-- | The name of the @Expression@ to delete.
deleteExpression_expressionName :: Lens.Lens' DeleteExpression Prelude.Text
deleteExpression_expressionName :: Lens' DeleteExpression Text
deleteExpression_expressionName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteExpression' {Text
expressionName :: Text
$sel:expressionName:DeleteExpression' :: DeleteExpression -> Text
expressionName} -> Text
expressionName) (\s :: DeleteExpression
s@DeleteExpression' {} Text
a -> DeleteExpression
s {$sel:expressionName:DeleteExpression' :: Text
expressionName = Text
a} :: DeleteExpression)

instance Core.AWSRequest DeleteExpression where
  type
    AWSResponse DeleteExpression =
      DeleteExpressionResponse
  request :: (Service -> Service)
-> DeleteExpression -> Request DeleteExpression
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteExpression
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteExpression)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"DeleteExpressionResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int -> ExpressionStatus -> DeleteExpressionResponse
DeleteExpressionResponse'
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"Expression")
      )

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

instance Prelude.NFData DeleteExpression where
  rnf :: DeleteExpression -> ()
rnf DeleteExpression' {Text
expressionName :: Text
domainName :: Text
$sel:expressionName:DeleteExpression' :: DeleteExpression -> Text
$sel:domainName:DeleteExpression' :: DeleteExpression -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
domainName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
expressionName

instance Data.ToHeaders DeleteExpression where
  toHeaders :: DeleteExpression -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery DeleteExpression where
  toQuery :: DeleteExpression -> QueryString
toQuery DeleteExpression' {Text
expressionName :: Text
domainName :: Text
$sel:expressionName:DeleteExpression' :: DeleteExpression -> Text
$sel:domainName:DeleteExpression' :: DeleteExpression -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DeleteExpression" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2013-01-01" :: Prelude.ByteString),
        ByteString
"DomainName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
domainName,
        ByteString
"ExpressionName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
expressionName
      ]

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

-- |
-- Create a value of 'DeleteExpressionResponse' 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', 'deleteExpressionResponse_httpStatus' - The response's http status code.
--
-- 'expression', 'deleteExpressionResponse_expression' - The status of the expression being deleted.
newDeleteExpressionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'expression'
  ExpressionStatus ->
  DeleteExpressionResponse
newDeleteExpressionResponse :: Int -> ExpressionStatus -> DeleteExpressionResponse
newDeleteExpressionResponse Int
pHttpStatus_ ExpressionStatus
pExpression_ =
  DeleteExpressionResponse'
    { $sel:httpStatus:DeleteExpressionResponse' :: Int
httpStatus =
        Int
pHttpStatus_,
      $sel:expression:DeleteExpressionResponse' :: ExpressionStatus
expression = ExpressionStatus
pExpression_
    }

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

-- | The status of the expression being deleted.
deleteExpressionResponse_expression :: Lens.Lens' DeleteExpressionResponse ExpressionStatus
deleteExpressionResponse_expression :: Lens' DeleteExpressionResponse ExpressionStatus
deleteExpressionResponse_expression = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteExpressionResponse' {ExpressionStatus
expression :: ExpressionStatus
$sel:expression:DeleteExpressionResponse' :: DeleteExpressionResponse -> ExpressionStatus
expression} -> ExpressionStatus
expression) (\s :: DeleteExpressionResponse
s@DeleteExpressionResponse' {} ExpressionStatus
a -> DeleteExpressionResponse
s {$sel:expression:DeleteExpressionResponse' :: ExpressionStatus
expression = ExpressionStatus
a} :: DeleteExpressionResponse)

instance Prelude.NFData DeleteExpressionResponse where
  rnf :: DeleteExpressionResponse -> ()
rnf DeleteExpressionResponse' {Int
ExpressionStatus
expression :: ExpressionStatus
httpStatus :: Int
$sel:expression:DeleteExpressionResponse' :: DeleteExpressionResponse -> ExpressionStatus
$sel:httpStatus:DeleteExpressionResponse' :: DeleteExpressionResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ExpressionStatus
expression