{-# 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 #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.EC2.DeleteFpgaImage
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes the specified Amazon FPGA Image (AFI).
module Amazonka.EC2.DeleteFpgaImage
  ( -- * Creating a Request
    DeleteFpgaImage (..),
    newDeleteFpgaImage,

    -- * Request Lenses
    deleteFpgaImage_dryRun,
    deleteFpgaImage_fpgaImageId,

    -- * Destructuring the Response
    DeleteFpgaImageResponse (..),
    newDeleteFpgaImageResponse,

    -- * Response Lenses
    deleteFpgaImageResponse_return,
    deleteFpgaImageResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EC2.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDeleteFpgaImage' smart constructor.
data DeleteFpgaImage = DeleteFpgaImage'
  { -- | Checks whether you have the required permissions for the action, without
    -- actually making the request, and provides an error response. If you have
    -- the required permissions, the error response is @DryRunOperation@.
    -- Otherwise, it is @UnauthorizedOperation@.
    DeleteFpgaImage -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the AFI.
    DeleteFpgaImage -> Text
fpgaImageId :: Prelude.Text
  }
  deriving (DeleteFpgaImage -> DeleteFpgaImage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteFpgaImage -> DeleteFpgaImage -> Bool
$c/= :: DeleteFpgaImage -> DeleteFpgaImage -> Bool
== :: DeleteFpgaImage -> DeleteFpgaImage -> Bool
$c== :: DeleteFpgaImage -> DeleteFpgaImage -> Bool
Prelude.Eq, ReadPrec [DeleteFpgaImage]
ReadPrec DeleteFpgaImage
Int -> ReadS DeleteFpgaImage
ReadS [DeleteFpgaImage]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteFpgaImage]
$creadListPrec :: ReadPrec [DeleteFpgaImage]
readPrec :: ReadPrec DeleteFpgaImage
$creadPrec :: ReadPrec DeleteFpgaImage
readList :: ReadS [DeleteFpgaImage]
$creadList :: ReadS [DeleteFpgaImage]
readsPrec :: Int -> ReadS DeleteFpgaImage
$creadsPrec :: Int -> ReadS DeleteFpgaImage
Prelude.Read, Int -> DeleteFpgaImage -> ShowS
[DeleteFpgaImage] -> ShowS
DeleteFpgaImage -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteFpgaImage] -> ShowS
$cshowList :: [DeleteFpgaImage] -> ShowS
show :: DeleteFpgaImage -> String
$cshow :: DeleteFpgaImage -> String
showsPrec :: Int -> DeleteFpgaImage -> ShowS
$cshowsPrec :: Int -> DeleteFpgaImage -> ShowS
Prelude.Show, forall x. Rep DeleteFpgaImage x -> DeleteFpgaImage
forall x. DeleteFpgaImage -> Rep DeleteFpgaImage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteFpgaImage x -> DeleteFpgaImage
$cfrom :: forall x. DeleteFpgaImage -> Rep DeleteFpgaImage x
Prelude.Generic)

-- |
-- Create a value of 'DeleteFpgaImage' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'dryRun', 'deleteFpgaImage_dryRun' - Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
--
-- 'fpgaImageId', 'deleteFpgaImage_fpgaImageId' - The ID of the AFI.
newDeleteFpgaImage ::
  -- | 'fpgaImageId'
  Prelude.Text ->
  DeleteFpgaImage
newDeleteFpgaImage :: Text -> DeleteFpgaImage
newDeleteFpgaImage Text
pFpgaImageId_ =
  DeleteFpgaImage'
    { $sel:dryRun:DeleteFpgaImage' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:fpgaImageId:DeleteFpgaImage' :: Text
fpgaImageId = Text
pFpgaImageId_
    }

-- | Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
deleteFpgaImage_dryRun :: Lens.Lens' DeleteFpgaImage (Prelude.Maybe Prelude.Bool)
deleteFpgaImage_dryRun :: Lens' DeleteFpgaImage (Maybe Bool)
deleteFpgaImage_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteFpgaImage' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:DeleteFpgaImage' :: DeleteFpgaImage -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: DeleteFpgaImage
s@DeleteFpgaImage' {} Maybe Bool
a -> DeleteFpgaImage
s {$sel:dryRun:DeleteFpgaImage' :: Maybe Bool
dryRun = Maybe Bool
a} :: DeleteFpgaImage)

-- | The ID of the AFI.
deleteFpgaImage_fpgaImageId :: Lens.Lens' DeleteFpgaImage Prelude.Text
deleteFpgaImage_fpgaImageId :: Lens' DeleteFpgaImage Text
deleteFpgaImage_fpgaImageId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteFpgaImage' {Text
fpgaImageId :: Text
$sel:fpgaImageId:DeleteFpgaImage' :: DeleteFpgaImage -> Text
fpgaImageId} -> Text
fpgaImageId) (\s :: DeleteFpgaImage
s@DeleteFpgaImage' {} Text
a -> DeleteFpgaImage
s {$sel:fpgaImageId:DeleteFpgaImage' :: Text
fpgaImageId = Text
a} :: DeleteFpgaImage)

instance Core.AWSRequest DeleteFpgaImage where
  type
    AWSResponse DeleteFpgaImage =
      DeleteFpgaImageResponse
  request :: (Service -> Service) -> DeleteFpgaImage -> Request DeleteFpgaImage
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteFpgaImage
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteFpgaImage)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Bool -> Int -> DeleteFpgaImageResponse
DeleteFpgaImageResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"return")
            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 DeleteFpgaImage where
  hashWithSalt :: Int -> DeleteFpgaImage -> Int
hashWithSalt Int
_salt DeleteFpgaImage' {Maybe Bool
Text
fpgaImageId :: Text
dryRun :: Maybe Bool
$sel:fpgaImageId:DeleteFpgaImage' :: DeleteFpgaImage -> Text
$sel:dryRun:DeleteFpgaImage' :: DeleteFpgaImage -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
fpgaImageId

instance Prelude.NFData DeleteFpgaImage where
  rnf :: DeleteFpgaImage -> ()
rnf DeleteFpgaImage' {Maybe Bool
Text
fpgaImageId :: Text
dryRun :: Maybe Bool
$sel:fpgaImageId:DeleteFpgaImage' :: DeleteFpgaImage -> Text
$sel:dryRun:DeleteFpgaImage' :: DeleteFpgaImage -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dryRun
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
fpgaImageId

instance Data.ToHeaders DeleteFpgaImage where
  toHeaders :: DeleteFpgaImage -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath DeleteFpgaImage where
  toPath :: DeleteFpgaImage -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery DeleteFpgaImage where
  toQuery :: DeleteFpgaImage -> QueryString
toQuery DeleteFpgaImage' {Maybe Bool
Text
fpgaImageId :: Text
dryRun :: Maybe Bool
$sel:fpgaImageId:DeleteFpgaImage' :: DeleteFpgaImage -> Text
$sel:dryRun:DeleteFpgaImage' :: DeleteFpgaImage -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DeleteFpgaImage" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        ByteString
"FpgaImageId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
fpgaImageId
      ]

-- | /See:/ 'newDeleteFpgaImageResponse' smart constructor.
data DeleteFpgaImageResponse = DeleteFpgaImageResponse'
  { -- | Is @true@ if the request succeeds, and an error otherwise.
    DeleteFpgaImageResponse -> Maybe Bool
return' :: Prelude.Maybe Prelude.Bool,
    -- | The response's http status code.
    DeleteFpgaImageResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteFpgaImageResponse -> DeleteFpgaImageResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteFpgaImageResponse -> DeleteFpgaImageResponse -> Bool
$c/= :: DeleteFpgaImageResponse -> DeleteFpgaImageResponse -> Bool
== :: DeleteFpgaImageResponse -> DeleteFpgaImageResponse -> Bool
$c== :: DeleteFpgaImageResponse -> DeleteFpgaImageResponse -> Bool
Prelude.Eq, ReadPrec [DeleteFpgaImageResponse]
ReadPrec DeleteFpgaImageResponse
Int -> ReadS DeleteFpgaImageResponse
ReadS [DeleteFpgaImageResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteFpgaImageResponse]
$creadListPrec :: ReadPrec [DeleteFpgaImageResponse]
readPrec :: ReadPrec DeleteFpgaImageResponse
$creadPrec :: ReadPrec DeleteFpgaImageResponse
readList :: ReadS [DeleteFpgaImageResponse]
$creadList :: ReadS [DeleteFpgaImageResponse]
readsPrec :: Int -> ReadS DeleteFpgaImageResponse
$creadsPrec :: Int -> ReadS DeleteFpgaImageResponse
Prelude.Read, Int -> DeleteFpgaImageResponse -> ShowS
[DeleteFpgaImageResponse] -> ShowS
DeleteFpgaImageResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteFpgaImageResponse] -> ShowS
$cshowList :: [DeleteFpgaImageResponse] -> ShowS
show :: DeleteFpgaImageResponse -> String
$cshow :: DeleteFpgaImageResponse -> String
showsPrec :: Int -> DeleteFpgaImageResponse -> ShowS
$cshowsPrec :: Int -> DeleteFpgaImageResponse -> ShowS
Prelude.Show, forall x. Rep DeleteFpgaImageResponse x -> DeleteFpgaImageResponse
forall x. DeleteFpgaImageResponse -> Rep DeleteFpgaImageResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteFpgaImageResponse x -> DeleteFpgaImageResponse
$cfrom :: forall x. DeleteFpgaImageResponse -> Rep DeleteFpgaImageResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteFpgaImageResponse' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'return'', 'deleteFpgaImageResponse_return' - Is @true@ if the request succeeds, and an error otherwise.
--
-- 'httpStatus', 'deleteFpgaImageResponse_httpStatus' - The response's http status code.
newDeleteFpgaImageResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteFpgaImageResponse
newDeleteFpgaImageResponse :: Int -> DeleteFpgaImageResponse
newDeleteFpgaImageResponse Int
pHttpStatus_ =
  DeleteFpgaImageResponse'
    { $sel:return':DeleteFpgaImageResponse' :: Maybe Bool
return' = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteFpgaImageResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Is @true@ if the request succeeds, and an error otherwise.
deleteFpgaImageResponse_return :: Lens.Lens' DeleteFpgaImageResponse (Prelude.Maybe Prelude.Bool)
deleteFpgaImageResponse_return :: Lens' DeleteFpgaImageResponse (Maybe Bool)
deleteFpgaImageResponse_return = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteFpgaImageResponse' {Maybe Bool
return' :: Maybe Bool
$sel:return':DeleteFpgaImageResponse' :: DeleteFpgaImageResponse -> Maybe Bool
return'} -> Maybe Bool
return') (\s :: DeleteFpgaImageResponse
s@DeleteFpgaImageResponse' {} Maybe Bool
a -> DeleteFpgaImageResponse
s {$sel:return':DeleteFpgaImageResponse' :: Maybe Bool
return' = Maybe Bool
a} :: DeleteFpgaImageResponse)

-- | The response's http status code.
deleteFpgaImageResponse_httpStatus :: Lens.Lens' DeleteFpgaImageResponse Prelude.Int
deleteFpgaImageResponse_httpStatus :: Lens' DeleteFpgaImageResponse Int
deleteFpgaImageResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteFpgaImageResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteFpgaImageResponse' :: DeleteFpgaImageResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DeleteFpgaImageResponse
s@DeleteFpgaImageResponse' {} Int
a -> DeleteFpgaImageResponse
s {$sel:httpStatus:DeleteFpgaImageResponse' :: Int
httpStatus = Int
a} :: DeleteFpgaImageResponse)

instance Prelude.NFData DeleteFpgaImageResponse where
  rnf :: DeleteFpgaImageResponse -> ()
rnf DeleteFpgaImageResponse' {Int
Maybe Bool
httpStatus :: Int
return' :: Maybe Bool
$sel:httpStatus:DeleteFpgaImageResponse' :: DeleteFpgaImageResponse -> Int
$sel:return':DeleteFpgaImageResponse' :: DeleteFpgaImageResponse -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
return'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus