{-# 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.SageMakerGeoSpatial.DeleteVectorEnrichmentJob
(
DeleteVectorEnrichmentJob (..),
newDeleteVectorEnrichmentJob,
deleteVectorEnrichmentJob_arn,
DeleteVectorEnrichmentJobResponse (..),
newDeleteVectorEnrichmentJobResponse,
deleteVectorEnrichmentJobResponse_httpStatus,
)
where
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
import Amazonka.SageMakerGeoSpatial.Types
data DeleteVectorEnrichmentJob = DeleteVectorEnrichmentJob'
{
DeleteVectorEnrichmentJob -> Text
arn :: Prelude.Text
}
deriving (DeleteVectorEnrichmentJob -> DeleteVectorEnrichmentJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteVectorEnrichmentJob -> DeleteVectorEnrichmentJob -> Bool
$c/= :: DeleteVectorEnrichmentJob -> DeleteVectorEnrichmentJob -> Bool
== :: DeleteVectorEnrichmentJob -> DeleteVectorEnrichmentJob -> Bool
$c== :: DeleteVectorEnrichmentJob -> DeleteVectorEnrichmentJob -> Bool
Prelude.Eq, ReadPrec [DeleteVectorEnrichmentJob]
ReadPrec DeleteVectorEnrichmentJob
Int -> ReadS DeleteVectorEnrichmentJob
ReadS [DeleteVectorEnrichmentJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteVectorEnrichmentJob]
$creadListPrec :: ReadPrec [DeleteVectorEnrichmentJob]
readPrec :: ReadPrec DeleteVectorEnrichmentJob
$creadPrec :: ReadPrec DeleteVectorEnrichmentJob
readList :: ReadS [DeleteVectorEnrichmentJob]
$creadList :: ReadS [DeleteVectorEnrichmentJob]
readsPrec :: Int -> ReadS DeleteVectorEnrichmentJob
$creadsPrec :: Int -> ReadS DeleteVectorEnrichmentJob
Prelude.Read, Int -> DeleteVectorEnrichmentJob -> ShowS
[DeleteVectorEnrichmentJob] -> ShowS
DeleteVectorEnrichmentJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteVectorEnrichmentJob] -> ShowS
$cshowList :: [DeleteVectorEnrichmentJob] -> ShowS
show :: DeleteVectorEnrichmentJob -> String
$cshow :: DeleteVectorEnrichmentJob -> String
showsPrec :: Int -> DeleteVectorEnrichmentJob -> ShowS
$cshowsPrec :: Int -> DeleteVectorEnrichmentJob -> ShowS
Prelude.Show, forall x.
Rep DeleteVectorEnrichmentJob x -> DeleteVectorEnrichmentJob
forall x.
DeleteVectorEnrichmentJob -> Rep DeleteVectorEnrichmentJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteVectorEnrichmentJob x -> DeleteVectorEnrichmentJob
$cfrom :: forall x.
DeleteVectorEnrichmentJob -> Rep DeleteVectorEnrichmentJob x
Prelude.Generic)
newDeleteVectorEnrichmentJob ::
Prelude.Text ->
DeleteVectorEnrichmentJob
newDeleteVectorEnrichmentJob :: Text -> DeleteVectorEnrichmentJob
newDeleteVectorEnrichmentJob Text
pArn_ =
DeleteVectorEnrichmentJob' {$sel:arn:DeleteVectorEnrichmentJob' :: Text
arn = Text
pArn_}
deleteVectorEnrichmentJob_arn :: Lens.Lens' DeleteVectorEnrichmentJob Prelude.Text
deleteVectorEnrichmentJob_arn :: Lens' DeleteVectorEnrichmentJob Text
deleteVectorEnrichmentJob_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteVectorEnrichmentJob' {Text
arn :: Text
$sel:arn:DeleteVectorEnrichmentJob' :: DeleteVectorEnrichmentJob -> Text
arn} -> Text
arn) (\s :: DeleteVectorEnrichmentJob
s@DeleteVectorEnrichmentJob' {} Text
a -> DeleteVectorEnrichmentJob
s {$sel:arn:DeleteVectorEnrichmentJob' :: Text
arn = Text
a} :: DeleteVectorEnrichmentJob)
instance Core.AWSRequest DeleteVectorEnrichmentJob where
type
AWSResponse DeleteVectorEnrichmentJob =
DeleteVectorEnrichmentJobResponse
request :: (Service -> Service)
-> DeleteVectorEnrichmentJob -> Request DeleteVectorEnrichmentJob
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 DeleteVectorEnrichmentJob
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse DeleteVectorEnrichmentJob)))
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 -> DeleteVectorEnrichmentJobResponse
DeleteVectorEnrichmentJobResponse'
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 DeleteVectorEnrichmentJob where
hashWithSalt :: Int -> DeleteVectorEnrichmentJob -> Int
hashWithSalt Int
_salt DeleteVectorEnrichmentJob' {Text
arn :: Text
$sel:arn:DeleteVectorEnrichmentJob' :: DeleteVectorEnrichmentJob -> Text
..} =
Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
arn
instance Prelude.NFData DeleteVectorEnrichmentJob where
rnf :: DeleteVectorEnrichmentJob -> ()
rnf DeleteVectorEnrichmentJob' {Text
arn :: Text
$sel:arn:DeleteVectorEnrichmentJob' :: DeleteVectorEnrichmentJob -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
arn
instance Data.ToHeaders DeleteVectorEnrichmentJob where
toHeaders :: DeleteVectorEnrichmentJob -> 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 DeleteVectorEnrichmentJob where
toPath :: DeleteVectorEnrichmentJob -> ByteString
toPath DeleteVectorEnrichmentJob' {Text
arn :: Text
$sel:arn:DeleteVectorEnrichmentJob' :: DeleteVectorEnrichmentJob -> Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ByteString
"/vector-enrichment-jobs/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
arn]
instance Data.ToQuery DeleteVectorEnrichmentJob where
toQuery :: DeleteVectorEnrichmentJob -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data DeleteVectorEnrichmentJobResponse = DeleteVectorEnrichmentJobResponse'
{
DeleteVectorEnrichmentJobResponse -> Int
httpStatus :: Prelude.Int
}
deriving (DeleteVectorEnrichmentJobResponse
-> DeleteVectorEnrichmentJobResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteVectorEnrichmentJobResponse
-> DeleteVectorEnrichmentJobResponse -> Bool
$c/= :: DeleteVectorEnrichmentJobResponse
-> DeleteVectorEnrichmentJobResponse -> Bool
== :: DeleteVectorEnrichmentJobResponse
-> DeleteVectorEnrichmentJobResponse -> Bool
$c== :: DeleteVectorEnrichmentJobResponse
-> DeleteVectorEnrichmentJobResponse -> Bool
Prelude.Eq, ReadPrec [DeleteVectorEnrichmentJobResponse]
ReadPrec DeleteVectorEnrichmentJobResponse
Int -> ReadS DeleteVectorEnrichmentJobResponse
ReadS [DeleteVectorEnrichmentJobResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteVectorEnrichmentJobResponse]
$creadListPrec :: ReadPrec [DeleteVectorEnrichmentJobResponse]
readPrec :: ReadPrec DeleteVectorEnrichmentJobResponse
$creadPrec :: ReadPrec DeleteVectorEnrichmentJobResponse
readList :: ReadS [DeleteVectorEnrichmentJobResponse]
$creadList :: ReadS [DeleteVectorEnrichmentJobResponse]
readsPrec :: Int -> ReadS DeleteVectorEnrichmentJobResponse
$creadsPrec :: Int -> ReadS DeleteVectorEnrichmentJobResponse
Prelude.Read, Int -> DeleteVectorEnrichmentJobResponse -> ShowS
[DeleteVectorEnrichmentJobResponse] -> ShowS
DeleteVectorEnrichmentJobResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteVectorEnrichmentJobResponse] -> ShowS
$cshowList :: [DeleteVectorEnrichmentJobResponse] -> ShowS
show :: DeleteVectorEnrichmentJobResponse -> String
$cshow :: DeleteVectorEnrichmentJobResponse -> String
showsPrec :: Int -> DeleteVectorEnrichmentJobResponse -> ShowS
$cshowsPrec :: Int -> DeleteVectorEnrichmentJobResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteVectorEnrichmentJobResponse x
-> DeleteVectorEnrichmentJobResponse
forall x.
DeleteVectorEnrichmentJobResponse
-> Rep DeleteVectorEnrichmentJobResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteVectorEnrichmentJobResponse x
-> DeleteVectorEnrichmentJobResponse
$cfrom :: forall x.
DeleteVectorEnrichmentJobResponse
-> Rep DeleteVectorEnrichmentJobResponse x
Prelude.Generic)
newDeleteVectorEnrichmentJobResponse ::
Prelude.Int ->
DeleteVectorEnrichmentJobResponse
newDeleteVectorEnrichmentJobResponse :: Int -> DeleteVectorEnrichmentJobResponse
newDeleteVectorEnrichmentJobResponse Int
pHttpStatus_ =
DeleteVectorEnrichmentJobResponse'
{ $sel:httpStatus:DeleteVectorEnrichmentJobResponse' :: Int
httpStatus =
Int
pHttpStatus_
}
deleteVectorEnrichmentJobResponse_httpStatus :: Lens.Lens' DeleteVectorEnrichmentJobResponse Prelude.Int
deleteVectorEnrichmentJobResponse_httpStatus :: Lens' DeleteVectorEnrichmentJobResponse Int
deleteVectorEnrichmentJobResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteVectorEnrichmentJobResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteVectorEnrichmentJobResponse' :: DeleteVectorEnrichmentJobResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DeleteVectorEnrichmentJobResponse
s@DeleteVectorEnrichmentJobResponse' {} Int
a -> DeleteVectorEnrichmentJobResponse
s {$sel:httpStatus:DeleteVectorEnrichmentJobResponse' :: Int
httpStatus = Int
a} :: DeleteVectorEnrichmentJobResponse)
instance
Prelude.NFData
DeleteVectorEnrichmentJobResponse
where
rnf :: DeleteVectorEnrichmentJobResponse -> ()
rnf DeleteVectorEnrichmentJobResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteVectorEnrichmentJobResponse' :: DeleteVectorEnrichmentJobResponse -> Int
..} =
forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus