{-# 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.Evidently.DeleteFeature
-- 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 an Evidently feature.
module Amazonka.Evidently.DeleteFeature
  ( -- * Creating a Request
    DeleteFeature (..),
    newDeleteFeature,

    -- * Request Lenses
    deleteFeature_feature,
    deleteFeature_project,

    -- * Destructuring the Response
    DeleteFeatureResponse (..),
    newDeleteFeatureResponse,

    -- * Response Lenses
    deleteFeatureResponse_httpStatus,
  )
where

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

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

-- |
-- Create a value of 'DeleteFeature' 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:
--
-- 'feature', 'deleteFeature_feature' - The name of the feature to delete.
--
-- 'project', 'deleteFeature_project' - The name or ARN of the project that contains the feature to delete.
newDeleteFeature ::
  -- | 'feature'
  Prelude.Text ->
  -- | 'project'
  Prelude.Text ->
  DeleteFeature
newDeleteFeature :: Text -> Text -> DeleteFeature
newDeleteFeature Text
pFeature_ Text
pProject_ =
  DeleteFeature'
    { $sel:feature:DeleteFeature' :: Text
feature = Text
pFeature_,
      $sel:project:DeleteFeature' :: Text
project = Text
pProject_
    }

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

-- | The name or ARN of the project that contains the feature to delete.
deleteFeature_project :: Lens.Lens' DeleteFeature Prelude.Text
deleteFeature_project :: Lens' DeleteFeature Text
deleteFeature_project = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteFeature' {Text
project :: Text
$sel:project:DeleteFeature' :: DeleteFeature -> Text
project} -> Text
project) (\s :: DeleteFeature
s@DeleteFeature' {} Text
a -> DeleteFeature
s {$sel:project:DeleteFeature' :: Text
project = Text
a} :: DeleteFeature)

instance Core.AWSRequest DeleteFeature where
  type
    AWSResponse DeleteFeature =
      DeleteFeatureResponse
  request :: (Service -> Service) -> DeleteFeature -> Request DeleteFeature
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteFeature
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteFeature)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> DeleteFeatureResponse
DeleteFeatureResponse'
            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))
      )

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

instance Prelude.NFData DeleteFeature where
  rnf :: DeleteFeature -> ()
rnf DeleteFeature' {Text
project :: Text
feature :: Text
$sel:project:DeleteFeature' :: DeleteFeature -> Text
$sel:feature:DeleteFeature' :: DeleteFeature -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
feature
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
project

instance Data.ToHeaders DeleteFeature where
  toHeaders :: DeleteFeature -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath DeleteFeature where
  toPath :: DeleteFeature -> ByteString
toPath DeleteFeature' {Text
project :: Text
feature :: Text
$sel:project:DeleteFeature' :: DeleteFeature -> Text
$sel:feature:DeleteFeature' :: DeleteFeature -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/projects/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
project,
        ByteString
"/features/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
feature
      ]

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

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

-- |
-- Create a value of 'DeleteFeatureResponse' 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', 'deleteFeatureResponse_httpStatus' - The response's http status code.
newDeleteFeatureResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteFeatureResponse
newDeleteFeatureResponse :: Int -> DeleteFeatureResponse
newDeleteFeatureResponse Int
pHttpStatus_ =
  DeleteFeatureResponse' {$sel:httpStatus:DeleteFeatureResponse' :: Int
httpStatus = Int
pHttpStatus_}

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

instance Prelude.NFData DeleteFeatureResponse where
  rnf :: DeleteFeatureResponse -> ()
rnf DeleteFeatureResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteFeatureResponse' :: DeleteFeatureResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus