{-# 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.GameLift.DeleteLocation
(
DeleteLocation (..),
newDeleteLocation,
deleteLocation_locationName,
DeleteLocationResponse (..),
newDeleteLocationResponse,
deleteLocationResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.GameLift.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data DeleteLocation = DeleteLocation'
{
DeleteLocation -> Text
locationName :: Prelude.Text
}
deriving (DeleteLocation -> DeleteLocation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteLocation -> DeleteLocation -> Bool
$c/= :: DeleteLocation -> DeleteLocation -> Bool
== :: DeleteLocation -> DeleteLocation -> Bool
$c== :: DeleteLocation -> DeleteLocation -> Bool
Prelude.Eq, ReadPrec [DeleteLocation]
ReadPrec DeleteLocation
Int -> ReadS DeleteLocation
ReadS [DeleteLocation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteLocation]
$creadListPrec :: ReadPrec [DeleteLocation]
readPrec :: ReadPrec DeleteLocation
$creadPrec :: ReadPrec DeleteLocation
readList :: ReadS [DeleteLocation]
$creadList :: ReadS [DeleteLocation]
readsPrec :: Int -> ReadS DeleteLocation
$creadsPrec :: Int -> ReadS DeleteLocation
Prelude.Read, Int -> DeleteLocation -> ShowS
[DeleteLocation] -> ShowS
DeleteLocation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteLocation] -> ShowS
$cshowList :: [DeleteLocation] -> ShowS
show :: DeleteLocation -> String
$cshow :: DeleteLocation -> String
showsPrec :: Int -> DeleteLocation -> ShowS
$cshowsPrec :: Int -> DeleteLocation -> ShowS
Prelude.Show, forall x. Rep DeleteLocation x -> DeleteLocation
forall x. DeleteLocation -> Rep DeleteLocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteLocation x -> DeleteLocation
$cfrom :: forall x. DeleteLocation -> Rep DeleteLocation x
Prelude.Generic)
newDeleteLocation ::
Prelude.Text ->
DeleteLocation
newDeleteLocation :: Text -> DeleteLocation
newDeleteLocation Text
pLocationName_ =
DeleteLocation' {$sel:locationName:DeleteLocation' :: Text
locationName = Text
pLocationName_}
deleteLocation_locationName :: Lens.Lens' DeleteLocation Prelude.Text
deleteLocation_locationName :: Lens' DeleteLocation Text
deleteLocation_locationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteLocation' {Text
locationName :: Text
$sel:locationName:DeleteLocation' :: DeleteLocation -> Text
locationName} -> Text
locationName) (\s :: DeleteLocation
s@DeleteLocation' {} Text
a -> DeleteLocation
s {$sel:locationName:DeleteLocation' :: Text
locationName = Text
a} :: DeleteLocation)
instance Core.AWSRequest DeleteLocation where
type
AWSResponse DeleteLocation =
DeleteLocationResponse
request :: (Service -> Service) -> DeleteLocation -> Request DeleteLocation
request Service -> Service
overrides =
forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteLocation
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteLocation)))
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 -> DeleteLocationResponse
DeleteLocationResponse'
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 DeleteLocation where
hashWithSalt :: Int -> DeleteLocation -> Int
hashWithSalt Int
_salt DeleteLocation' {Text
locationName :: Text
$sel:locationName:DeleteLocation' :: DeleteLocation -> Text
..} =
Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
locationName
instance Prelude.NFData DeleteLocation where
rnf :: DeleteLocation -> ()
rnf DeleteLocation' {Text
locationName :: Text
$sel:locationName:DeleteLocation' :: DeleteLocation -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
locationName
instance Data.ToHeaders DeleteLocation where
toHeaders :: DeleteLocation -> ResponseHeaders
toHeaders =
forall a b. a -> b -> a
Prelude.const
( forall a. Monoid a => [a] -> a
Prelude.mconcat
[ HeaderName
"X-Amz-Target"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# (ByteString
"GameLift.DeleteLocation" :: Prelude.ByteString),
HeaderName
"Content-Type"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
Prelude.ByteString
)
]
)
instance Data.ToJSON DeleteLocation where
toJSON :: DeleteLocation -> Value
toJSON DeleteLocation' {Text
locationName :: Text
$sel:locationName:DeleteLocation' :: DeleteLocation -> Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[forall a. a -> Maybe a
Prelude.Just (Key
"LocationName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
locationName)]
)
instance Data.ToPath DeleteLocation where
toPath :: DeleteLocation -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery DeleteLocation where
toQuery :: DeleteLocation -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data DeleteLocationResponse = DeleteLocationResponse'
{
DeleteLocationResponse -> Int
httpStatus :: Prelude.Int
}
deriving (DeleteLocationResponse -> DeleteLocationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteLocationResponse -> DeleteLocationResponse -> Bool
$c/= :: DeleteLocationResponse -> DeleteLocationResponse -> Bool
== :: DeleteLocationResponse -> DeleteLocationResponse -> Bool
$c== :: DeleteLocationResponse -> DeleteLocationResponse -> Bool
Prelude.Eq, ReadPrec [DeleteLocationResponse]
ReadPrec DeleteLocationResponse
Int -> ReadS DeleteLocationResponse
ReadS [DeleteLocationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteLocationResponse]
$creadListPrec :: ReadPrec [DeleteLocationResponse]
readPrec :: ReadPrec DeleteLocationResponse
$creadPrec :: ReadPrec DeleteLocationResponse
readList :: ReadS [DeleteLocationResponse]
$creadList :: ReadS [DeleteLocationResponse]
readsPrec :: Int -> ReadS DeleteLocationResponse
$creadsPrec :: Int -> ReadS DeleteLocationResponse
Prelude.Read, Int -> DeleteLocationResponse -> ShowS
[DeleteLocationResponse] -> ShowS
DeleteLocationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteLocationResponse] -> ShowS
$cshowList :: [DeleteLocationResponse] -> ShowS
show :: DeleteLocationResponse -> String
$cshow :: DeleteLocationResponse -> String
showsPrec :: Int -> DeleteLocationResponse -> ShowS
$cshowsPrec :: Int -> DeleteLocationResponse -> ShowS
Prelude.Show, forall x. Rep DeleteLocationResponse x -> DeleteLocationResponse
forall x. DeleteLocationResponse -> Rep DeleteLocationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteLocationResponse x -> DeleteLocationResponse
$cfrom :: forall x. DeleteLocationResponse -> Rep DeleteLocationResponse x
Prelude.Generic)
newDeleteLocationResponse ::
Prelude.Int ->
DeleteLocationResponse
newDeleteLocationResponse :: Int -> DeleteLocationResponse
newDeleteLocationResponse Int
pHttpStatus_ =
DeleteLocationResponse' {$sel:httpStatus:DeleteLocationResponse' :: Int
httpStatus = Int
pHttpStatus_}
deleteLocationResponse_httpStatus :: Lens.Lens' DeleteLocationResponse Prelude.Int
deleteLocationResponse_httpStatus :: Lens' DeleteLocationResponse Int
deleteLocationResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteLocationResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteLocationResponse' :: DeleteLocationResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DeleteLocationResponse
s@DeleteLocationResponse' {} Int
a -> DeleteLocationResponse
s {$sel:httpStatus:DeleteLocationResponse' :: Int
httpStatus = Int
a} :: DeleteLocationResponse)
instance Prelude.NFData DeleteLocationResponse where
rnf :: DeleteLocationResponse -> ()
rnf DeleteLocationResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteLocationResponse' :: DeleteLocationResponse -> Int
..} =
forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus