{-# 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.Connect.DeleteInstance
(
DeleteInstance (..),
newDeleteInstance,
deleteInstance_instanceId,
DeleteInstanceResponse (..),
newDeleteInstanceResponse,
)
where
import Amazonka.Connect.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
data DeleteInstance = DeleteInstance'
{
DeleteInstance -> Text
instanceId :: Prelude.Text
}
deriving (DeleteInstance -> DeleteInstance -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteInstance -> DeleteInstance -> Bool
$c/= :: DeleteInstance -> DeleteInstance -> Bool
== :: DeleteInstance -> DeleteInstance -> Bool
$c== :: DeleteInstance -> DeleteInstance -> Bool
Prelude.Eq, ReadPrec [DeleteInstance]
ReadPrec DeleteInstance
Int -> ReadS DeleteInstance
ReadS [DeleteInstance]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteInstance]
$creadListPrec :: ReadPrec [DeleteInstance]
readPrec :: ReadPrec DeleteInstance
$creadPrec :: ReadPrec DeleteInstance
readList :: ReadS [DeleteInstance]
$creadList :: ReadS [DeleteInstance]
readsPrec :: Int -> ReadS DeleteInstance
$creadsPrec :: Int -> ReadS DeleteInstance
Prelude.Read, Int -> DeleteInstance -> ShowS
[DeleteInstance] -> ShowS
DeleteInstance -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteInstance] -> ShowS
$cshowList :: [DeleteInstance] -> ShowS
show :: DeleteInstance -> String
$cshow :: DeleteInstance -> String
showsPrec :: Int -> DeleteInstance -> ShowS
$cshowsPrec :: Int -> DeleteInstance -> ShowS
Prelude.Show, forall x. Rep DeleteInstance x -> DeleteInstance
forall x. DeleteInstance -> Rep DeleteInstance x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteInstance x -> DeleteInstance
$cfrom :: forall x. DeleteInstance -> Rep DeleteInstance x
Prelude.Generic)
newDeleteInstance ::
Prelude.Text ->
DeleteInstance
newDeleteInstance :: Text -> DeleteInstance
newDeleteInstance Text
pInstanceId_ =
DeleteInstance' {$sel:instanceId:DeleteInstance' :: Text
instanceId = Text
pInstanceId_}
deleteInstance_instanceId :: Lens.Lens' DeleteInstance Prelude.Text
deleteInstance_instanceId :: Lens' DeleteInstance Text
deleteInstance_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteInstance' {Text
instanceId :: Text
$sel:instanceId:DeleteInstance' :: DeleteInstance -> Text
instanceId} -> Text
instanceId) (\s :: DeleteInstance
s@DeleteInstance' {} Text
a -> DeleteInstance
s {$sel:instanceId:DeleteInstance' :: Text
instanceId = Text
a} :: DeleteInstance)
instance Core.AWSRequest DeleteInstance where
type
AWSResponse DeleteInstance =
DeleteInstanceResponse
request :: (Service -> Service) -> DeleteInstance -> Request DeleteInstance
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 DeleteInstance
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteInstance)))
response =
forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull DeleteInstanceResponse
DeleteInstanceResponse'
instance Prelude.Hashable DeleteInstance where
hashWithSalt :: Int -> DeleteInstance -> Int
hashWithSalt Int
_salt DeleteInstance' {Text
instanceId :: Text
$sel:instanceId:DeleteInstance' :: DeleteInstance -> Text
..} =
Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId
instance Prelude.NFData DeleteInstance where
rnf :: DeleteInstance -> ()
rnf DeleteInstance' {Text
instanceId :: Text
$sel:instanceId:DeleteInstance' :: DeleteInstance -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
instanceId
instance Data.ToHeaders DeleteInstance where
toHeaders :: DeleteInstance -> [Header]
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 -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
Prelude.ByteString
)
]
)
instance Data.ToPath DeleteInstance where
toPath :: DeleteInstance -> ByteString
toPath DeleteInstance' {Text
instanceId :: Text
$sel:instanceId:DeleteInstance' :: DeleteInstance -> Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ByteString
"/instance/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
instanceId]
instance Data.ToQuery DeleteInstance where
toQuery :: DeleteInstance -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data DeleteInstanceResponse = DeleteInstanceResponse'
{
}
deriving (DeleteInstanceResponse -> DeleteInstanceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteInstanceResponse -> DeleteInstanceResponse -> Bool
$c/= :: DeleteInstanceResponse -> DeleteInstanceResponse -> Bool
== :: DeleteInstanceResponse -> DeleteInstanceResponse -> Bool
$c== :: DeleteInstanceResponse -> DeleteInstanceResponse -> Bool
Prelude.Eq, ReadPrec [DeleteInstanceResponse]
ReadPrec DeleteInstanceResponse
Int -> ReadS DeleteInstanceResponse
ReadS [DeleteInstanceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteInstanceResponse]
$creadListPrec :: ReadPrec [DeleteInstanceResponse]
readPrec :: ReadPrec DeleteInstanceResponse
$creadPrec :: ReadPrec DeleteInstanceResponse
readList :: ReadS [DeleteInstanceResponse]
$creadList :: ReadS [DeleteInstanceResponse]
readsPrec :: Int -> ReadS DeleteInstanceResponse
$creadsPrec :: Int -> ReadS DeleteInstanceResponse
Prelude.Read, Int -> DeleteInstanceResponse -> ShowS
[DeleteInstanceResponse] -> ShowS
DeleteInstanceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteInstanceResponse] -> ShowS
$cshowList :: [DeleteInstanceResponse] -> ShowS
show :: DeleteInstanceResponse -> String
$cshow :: DeleteInstanceResponse -> String
showsPrec :: Int -> DeleteInstanceResponse -> ShowS
$cshowsPrec :: Int -> DeleteInstanceResponse -> ShowS
Prelude.Show, forall x. Rep DeleteInstanceResponse x -> DeleteInstanceResponse
forall x. DeleteInstanceResponse -> Rep DeleteInstanceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteInstanceResponse x -> DeleteInstanceResponse
$cfrom :: forall x. DeleteInstanceResponse -> Rep DeleteInstanceResponse x
Prelude.Generic)
newDeleteInstanceResponse ::
DeleteInstanceResponse
newDeleteInstanceResponse :: DeleteInstanceResponse
newDeleteInstanceResponse = DeleteInstanceResponse
DeleteInstanceResponse'
instance Prelude.NFData DeleteInstanceResponse where
rnf :: DeleteInstanceResponse -> ()
rnf DeleteInstanceResponse
_ = ()