{-# 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.AppStream.DeleteImage
(
DeleteImage (..),
newDeleteImage,
deleteImage_name,
DeleteImageResponse (..),
newDeleteImageResponse,
deleteImageResponse_image,
deleteImageResponse_httpStatus,
)
where
import Amazonka.AppStream.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 DeleteImage = DeleteImage'
{
DeleteImage -> Text
name :: Prelude.Text
}
deriving (DeleteImage -> DeleteImage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteImage -> DeleteImage -> Bool
$c/= :: DeleteImage -> DeleteImage -> Bool
== :: DeleteImage -> DeleteImage -> Bool
$c== :: DeleteImage -> DeleteImage -> Bool
Prelude.Eq, ReadPrec [DeleteImage]
ReadPrec DeleteImage
Int -> ReadS DeleteImage
ReadS [DeleteImage]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteImage]
$creadListPrec :: ReadPrec [DeleteImage]
readPrec :: ReadPrec DeleteImage
$creadPrec :: ReadPrec DeleteImage
readList :: ReadS [DeleteImage]
$creadList :: ReadS [DeleteImage]
readsPrec :: Int -> ReadS DeleteImage
$creadsPrec :: Int -> ReadS DeleteImage
Prelude.Read, Int -> DeleteImage -> ShowS
[DeleteImage] -> ShowS
DeleteImage -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteImage] -> ShowS
$cshowList :: [DeleteImage] -> ShowS
show :: DeleteImage -> String
$cshow :: DeleteImage -> String
showsPrec :: Int -> DeleteImage -> ShowS
$cshowsPrec :: Int -> DeleteImage -> ShowS
Prelude.Show, forall x. Rep DeleteImage x -> DeleteImage
forall x. DeleteImage -> Rep DeleteImage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteImage x -> DeleteImage
$cfrom :: forall x. DeleteImage -> Rep DeleteImage x
Prelude.Generic)
newDeleteImage ::
Prelude.Text ->
DeleteImage
newDeleteImage :: Text -> DeleteImage
newDeleteImage Text
pName_ = DeleteImage' {$sel:name:DeleteImage' :: Text
name = Text
pName_}
deleteImage_name :: Lens.Lens' DeleteImage Prelude.Text
deleteImage_name :: Lens' DeleteImage Text
deleteImage_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteImage' {Text
name :: Text
$sel:name:DeleteImage' :: DeleteImage -> Text
name} -> Text
name) (\s :: DeleteImage
s@DeleteImage' {} Text
a -> DeleteImage
s {$sel:name:DeleteImage' :: Text
name = Text
a} :: DeleteImage)
instance Core.AWSRequest DeleteImage where
type AWSResponse DeleteImage = DeleteImageResponse
request :: (Service -> Service) -> DeleteImage -> Request DeleteImage
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 DeleteImage
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteImage)))
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 ->
Maybe Image -> Int -> DeleteImageResponse
DeleteImageResponse'
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Image")
forall (f :: * -> *) a b. Applicative f => 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 DeleteImage where
hashWithSalt :: Int -> DeleteImage -> Int
hashWithSalt Int
_salt DeleteImage' {Text
name :: Text
$sel:name:DeleteImage' :: DeleteImage -> Text
..} =
Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
instance Prelude.NFData DeleteImage where
rnf :: DeleteImage -> ()
rnf DeleteImage' {Text
name :: Text
$sel:name:DeleteImage' :: DeleteImage -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
name
instance Data.ToHeaders DeleteImage where
toHeaders :: DeleteImage -> 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
"PhotonAdminProxyService.DeleteImage" ::
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 DeleteImage where
toJSON :: DeleteImage -> Value
toJSON DeleteImage' {Text
name :: Text
$sel:name:DeleteImage' :: DeleteImage -> Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name)]
)
instance Data.ToPath DeleteImage where
toPath :: DeleteImage -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery DeleteImage where
toQuery :: DeleteImage -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data DeleteImageResponse = DeleteImageResponse'
{
DeleteImageResponse -> Maybe Image
image :: Prelude.Maybe Image,
DeleteImageResponse -> Int
httpStatus :: Prelude.Int
}
deriving (DeleteImageResponse -> DeleteImageResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteImageResponse -> DeleteImageResponse -> Bool
$c/= :: DeleteImageResponse -> DeleteImageResponse -> Bool
== :: DeleteImageResponse -> DeleteImageResponse -> Bool
$c== :: DeleteImageResponse -> DeleteImageResponse -> Bool
Prelude.Eq, ReadPrec [DeleteImageResponse]
ReadPrec DeleteImageResponse
Int -> ReadS DeleteImageResponse
ReadS [DeleteImageResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteImageResponse]
$creadListPrec :: ReadPrec [DeleteImageResponse]
readPrec :: ReadPrec DeleteImageResponse
$creadPrec :: ReadPrec DeleteImageResponse
readList :: ReadS [DeleteImageResponse]
$creadList :: ReadS [DeleteImageResponse]
readsPrec :: Int -> ReadS DeleteImageResponse
$creadsPrec :: Int -> ReadS DeleteImageResponse
Prelude.Read, Int -> DeleteImageResponse -> ShowS
[DeleteImageResponse] -> ShowS
DeleteImageResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteImageResponse] -> ShowS
$cshowList :: [DeleteImageResponse] -> ShowS
show :: DeleteImageResponse -> String
$cshow :: DeleteImageResponse -> String
showsPrec :: Int -> DeleteImageResponse -> ShowS
$cshowsPrec :: Int -> DeleteImageResponse -> ShowS
Prelude.Show, forall x. Rep DeleteImageResponse x -> DeleteImageResponse
forall x. DeleteImageResponse -> Rep DeleteImageResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteImageResponse x -> DeleteImageResponse
$cfrom :: forall x. DeleteImageResponse -> Rep DeleteImageResponse x
Prelude.Generic)
newDeleteImageResponse ::
Prelude.Int ->
DeleteImageResponse
newDeleteImageResponse :: Int -> DeleteImageResponse
newDeleteImageResponse Int
pHttpStatus_ =
DeleteImageResponse'
{ $sel:image:DeleteImageResponse' :: Maybe Image
image = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:DeleteImageResponse' :: Int
httpStatus = Int
pHttpStatus_
}
deleteImageResponse_image :: Lens.Lens' DeleteImageResponse (Prelude.Maybe Image)
deleteImageResponse_image :: Lens' DeleteImageResponse (Maybe Image)
deleteImageResponse_image = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteImageResponse' {Maybe Image
image :: Maybe Image
$sel:image:DeleteImageResponse' :: DeleteImageResponse -> Maybe Image
image} -> Maybe Image
image) (\s :: DeleteImageResponse
s@DeleteImageResponse' {} Maybe Image
a -> DeleteImageResponse
s {$sel:image:DeleteImageResponse' :: Maybe Image
image = Maybe Image
a} :: DeleteImageResponse)
deleteImageResponse_httpStatus :: Lens.Lens' DeleteImageResponse Prelude.Int
deleteImageResponse_httpStatus :: Lens' DeleteImageResponse Int
deleteImageResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteImageResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteImageResponse' :: DeleteImageResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DeleteImageResponse
s@DeleteImageResponse' {} Int
a -> DeleteImageResponse
s {$sel:httpStatus:DeleteImageResponse' :: Int
httpStatus = Int
a} :: DeleteImageResponse)
instance Prelude.NFData DeleteImageResponse where
rnf :: DeleteImageResponse -> ()
rnf DeleteImageResponse' {Int
Maybe Image
httpStatus :: Int
image :: Maybe Image
$sel:httpStatus:DeleteImageResponse' :: DeleteImageResponse -> Int
$sel:image:DeleteImageResponse' :: DeleteImageResponse -> Maybe Image
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Image
image
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus