{-# 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 #-}
module Amazonka.DataBrew.DeleteRecipeVersion
(
DeleteRecipeVersion (..),
newDeleteRecipeVersion,
deleteRecipeVersion_name,
deleteRecipeVersion_recipeVersion,
DeleteRecipeVersionResponse (..),
newDeleteRecipeVersionResponse,
deleteRecipeVersionResponse_httpStatus,
deleteRecipeVersionResponse_name,
deleteRecipeVersionResponse_recipeVersion,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.DataBrew.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data DeleteRecipeVersion = DeleteRecipeVersion'
{
DeleteRecipeVersion -> Text
name :: Prelude.Text,
DeleteRecipeVersion -> Text
recipeVersion :: Prelude.Text
}
deriving (DeleteRecipeVersion -> DeleteRecipeVersion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteRecipeVersion -> DeleteRecipeVersion -> Bool
$c/= :: DeleteRecipeVersion -> DeleteRecipeVersion -> Bool
== :: DeleteRecipeVersion -> DeleteRecipeVersion -> Bool
$c== :: DeleteRecipeVersion -> DeleteRecipeVersion -> Bool
Prelude.Eq, ReadPrec [DeleteRecipeVersion]
ReadPrec DeleteRecipeVersion
Int -> ReadS DeleteRecipeVersion
ReadS [DeleteRecipeVersion]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteRecipeVersion]
$creadListPrec :: ReadPrec [DeleteRecipeVersion]
readPrec :: ReadPrec DeleteRecipeVersion
$creadPrec :: ReadPrec DeleteRecipeVersion
readList :: ReadS [DeleteRecipeVersion]
$creadList :: ReadS [DeleteRecipeVersion]
readsPrec :: Int -> ReadS DeleteRecipeVersion
$creadsPrec :: Int -> ReadS DeleteRecipeVersion
Prelude.Read, Int -> DeleteRecipeVersion -> ShowS
[DeleteRecipeVersion] -> ShowS
DeleteRecipeVersion -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteRecipeVersion] -> ShowS
$cshowList :: [DeleteRecipeVersion] -> ShowS
show :: DeleteRecipeVersion -> String
$cshow :: DeleteRecipeVersion -> String
showsPrec :: Int -> DeleteRecipeVersion -> ShowS
$cshowsPrec :: Int -> DeleteRecipeVersion -> ShowS
Prelude.Show, forall x. Rep DeleteRecipeVersion x -> DeleteRecipeVersion
forall x. DeleteRecipeVersion -> Rep DeleteRecipeVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteRecipeVersion x -> DeleteRecipeVersion
$cfrom :: forall x. DeleteRecipeVersion -> Rep DeleteRecipeVersion x
Prelude.Generic)
newDeleteRecipeVersion ::
Prelude.Text ->
Prelude.Text ->
DeleteRecipeVersion
newDeleteRecipeVersion :: Text -> Text -> DeleteRecipeVersion
newDeleteRecipeVersion Text
pName_ Text
pRecipeVersion_ =
DeleteRecipeVersion'
{ $sel:name:DeleteRecipeVersion' :: Text
name = Text
pName_,
$sel:recipeVersion:DeleteRecipeVersion' :: Text
recipeVersion = Text
pRecipeVersion_
}
deleteRecipeVersion_name :: Lens.Lens' DeleteRecipeVersion Prelude.Text
deleteRecipeVersion_name :: Lens' DeleteRecipeVersion Text
deleteRecipeVersion_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteRecipeVersion' {Text
name :: Text
$sel:name:DeleteRecipeVersion' :: DeleteRecipeVersion -> Text
name} -> Text
name) (\s :: DeleteRecipeVersion
s@DeleteRecipeVersion' {} Text
a -> DeleteRecipeVersion
s {$sel:name:DeleteRecipeVersion' :: Text
name = Text
a} :: DeleteRecipeVersion)
deleteRecipeVersion_recipeVersion :: Lens.Lens' DeleteRecipeVersion Prelude.Text
deleteRecipeVersion_recipeVersion :: Lens' DeleteRecipeVersion Text
deleteRecipeVersion_recipeVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteRecipeVersion' {Text
recipeVersion :: Text
$sel:recipeVersion:DeleteRecipeVersion' :: DeleteRecipeVersion -> Text
recipeVersion} -> Text
recipeVersion) (\s :: DeleteRecipeVersion
s@DeleteRecipeVersion' {} Text
a -> DeleteRecipeVersion
s {$sel:recipeVersion:DeleteRecipeVersion' :: Text
recipeVersion = Text
a} :: DeleteRecipeVersion)
instance Core.AWSRequest DeleteRecipeVersion where
type
AWSResponse DeleteRecipeVersion =
DeleteRecipeVersionResponse
request :: (Service -> Service)
-> DeleteRecipeVersion -> Request DeleteRecipeVersion
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 DeleteRecipeVersion
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse DeleteRecipeVersion)))
response =
forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
( \Int
s ResponseHeaders
h Object
x ->
Int -> Text -> Text -> DeleteRecipeVersionResponse
DeleteRecipeVersionResponse'
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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"Name")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"RecipeVersion")
)
instance Prelude.Hashable DeleteRecipeVersion where
hashWithSalt :: Int -> DeleteRecipeVersion -> Int
hashWithSalt Int
_salt DeleteRecipeVersion' {Text
recipeVersion :: Text
name :: Text
$sel:recipeVersion:DeleteRecipeVersion' :: DeleteRecipeVersion -> Text
$sel:name:DeleteRecipeVersion' :: DeleteRecipeVersion -> Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
recipeVersion
instance Prelude.NFData DeleteRecipeVersion where
rnf :: DeleteRecipeVersion -> ()
rnf DeleteRecipeVersion' {Text
recipeVersion :: Text
name :: Text
$sel:recipeVersion:DeleteRecipeVersion' :: DeleteRecipeVersion -> Text
$sel:name:DeleteRecipeVersion' :: DeleteRecipeVersion -> Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Text
name
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
recipeVersion
instance Data.ToHeaders DeleteRecipeVersion where
toHeaders :: DeleteRecipeVersion -> 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 DeleteRecipeVersion where
toPath :: DeleteRecipeVersion -> ByteString
toPath DeleteRecipeVersion' {Text
recipeVersion :: Text
name :: Text
$sel:recipeVersion:DeleteRecipeVersion' :: DeleteRecipeVersion -> Text
$sel:name:DeleteRecipeVersion' :: DeleteRecipeVersion -> Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ ByteString
"/recipes/",
forall a. ToByteString a => a -> ByteString
Data.toBS Text
name,
ByteString
"/recipeVersion/",
forall a. ToByteString a => a -> ByteString
Data.toBS Text
recipeVersion
]
instance Data.ToQuery DeleteRecipeVersion where
toQuery :: DeleteRecipeVersion -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data DeleteRecipeVersionResponse = DeleteRecipeVersionResponse'
{
DeleteRecipeVersionResponse -> Int
httpStatus :: Prelude.Int,
DeleteRecipeVersionResponse -> Text
name :: Prelude.Text,
DeleteRecipeVersionResponse -> Text
recipeVersion :: Prelude.Text
}
deriving (DeleteRecipeVersionResponse -> DeleteRecipeVersionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteRecipeVersionResponse -> DeleteRecipeVersionResponse -> Bool
$c/= :: DeleteRecipeVersionResponse -> DeleteRecipeVersionResponse -> Bool
== :: DeleteRecipeVersionResponse -> DeleteRecipeVersionResponse -> Bool
$c== :: DeleteRecipeVersionResponse -> DeleteRecipeVersionResponse -> Bool
Prelude.Eq, ReadPrec [DeleteRecipeVersionResponse]
ReadPrec DeleteRecipeVersionResponse
Int -> ReadS DeleteRecipeVersionResponse
ReadS [DeleteRecipeVersionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteRecipeVersionResponse]
$creadListPrec :: ReadPrec [DeleteRecipeVersionResponse]
readPrec :: ReadPrec DeleteRecipeVersionResponse
$creadPrec :: ReadPrec DeleteRecipeVersionResponse
readList :: ReadS [DeleteRecipeVersionResponse]
$creadList :: ReadS [DeleteRecipeVersionResponse]
readsPrec :: Int -> ReadS DeleteRecipeVersionResponse
$creadsPrec :: Int -> ReadS DeleteRecipeVersionResponse
Prelude.Read, Int -> DeleteRecipeVersionResponse -> ShowS
[DeleteRecipeVersionResponse] -> ShowS
DeleteRecipeVersionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteRecipeVersionResponse] -> ShowS
$cshowList :: [DeleteRecipeVersionResponse] -> ShowS
show :: DeleteRecipeVersionResponse -> String
$cshow :: DeleteRecipeVersionResponse -> String
showsPrec :: Int -> DeleteRecipeVersionResponse -> ShowS
$cshowsPrec :: Int -> DeleteRecipeVersionResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteRecipeVersionResponse x -> DeleteRecipeVersionResponse
forall x.
DeleteRecipeVersionResponse -> Rep DeleteRecipeVersionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteRecipeVersionResponse x -> DeleteRecipeVersionResponse
$cfrom :: forall x.
DeleteRecipeVersionResponse -> Rep DeleteRecipeVersionResponse x
Prelude.Generic)
newDeleteRecipeVersionResponse ::
Prelude.Int ->
Prelude.Text ->
Prelude.Text ->
DeleteRecipeVersionResponse
newDeleteRecipeVersionResponse :: Int -> Text -> Text -> DeleteRecipeVersionResponse
newDeleteRecipeVersionResponse
Int
pHttpStatus_
Text
pName_
Text
pRecipeVersion_ =
DeleteRecipeVersionResponse'
{ $sel:httpStatus:DeleteRecipeVersionResponse' :: Int
httpStatus =
Int
pHttpStatus_,
$sel:name:DeleteRecipeVersionResponse' :: Text
name = Text
pName_,
$sel:recipeVersion:DeleteRecipeVersionResponse' :: Text
recipeVersion = Text
pRecipeVersion_
}
deleteRecipeVersionResponse_httpStatus :: Lens.Lens' DeleteRecipeVersionResponse Prelude.Int
deleteRecipeVersionResponse_httpStatus :: Lens' DeleteRecipeVersionResponse Int
deleteRecipeVersionResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteRecipeVersionResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteRecipeVersionResponse' :: DeleteRecipeVersionResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DeleteRecipeVersionResponse
s@DeleteRecipeVersionResponse' {} Int
a -> DeleteRecipeVersionResponse
s {$sel:httpStatus:DeleteRecipeVersionResponse' :: Int
httpStatus = Int
a} :: DeleteRecipeVersionResponse)
deleteRecipeVersionResponse_name :: Lens.Lens' DeleteRecipeVersionResponse Prelude.Text
deleteRecipeVersionResponse_name :: Lens' DeleteRecipeVersionResponse Text
deleteRecipeVersionResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteRecipeVersionResponse' {Text
name :: Text
$sel:name:DeleteRecipeVersionResponse' :: DeleteRecipeVersionResponse -> Text
name} -> Text
name) (\s :: DeleteRecipeVersionResponse
s@DeleteRecipeVersionResponse' {} Text
a -> DeleteRecipeVersionResponse
s {$sel:name:DeleteRecipeVersionResponse' :: Text
name = Text
a} :: DeleteRecipeVersionResponse)
deleteRecipeVersionResponse_recipeVersion :: Lens.Lens' DeleteRecipeVersionResponse Prelude.Text
deleteRecipeVersionResponse_recipeVersion :: Lens' DeleteRecipeVersionResponse Text
deleteRecipeVersionResponse_recipeVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteRecipeVersionResponse' {Text
recipeVersion :: Text
$sel:recipeVersion:DeleteRecipeVersionResponse' :: DeleteRecipeVersionResponse -> Text
recipeVersion} -> Text
recipeVersion) (\s :: DeleteRecipeVersionResponse
s@DeleteRecipeVersionResponse' {} Text
a -> DeleteRecipeVersionResponse
s {$sel:recipeVersion:DeleteRecipeVersionResponse' :: Text
recipeVersion = Text
a} :: DeleteRecipeVersionResponse)
instance Prelude.NFData DeleteRecipeVersionResponse where
rnf :: DeleteRecipeVersionResponse -> ()
rnf DeleteRecipeVersionResponse' {Int
Text
recipeVersion :: Text
name :: Text
httpStatus :: Int
$sel:recipeVersion:DeleteRecipeVersionResponse' :: DeleteRecipeVersionResponse -> Text
$sel:name:DeleteRecipeVersionResponse' :: DeleteRecipeVersionResponse -> Text
$sel:httpStatus:DeleteRecipeVersionResponse' :: DeleteRecipeVersionResponse -> 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 Text
name
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
recipeVersion