{-# 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.IoTWireless.DeleteFuotaTask
-- 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 a FUOTA task.
module Amazonka.IoTWireless.DeleteFuotaTask
  ( -- * Creating a Request
    DeleteFuotaTask (..),
    newDeleteFuotaTask,

    -- * Request Lenses
    deleteFuotaTask_id,

    -- * Destructuring the Response
    DeleteFuotaTaskResponse (..),
    newDeleteFuotaTaskResponse,

    -- * Response Lenses
    deleteFuotaTaskResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDeleteFuotaTask' smart constructor.
data DeleteFuotaTask = DeleteFuotaTask'
  { DeleteFuotaTask -> Text
id :: Prelude.Text
  }
  deriving (DeleteFuotaTask -> DeleteFuotaTask -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteFuotaTask -> DeleteFuotaTask -> Bool
$c/= :: DeleteFuotaTask -> DeleteFuotaTask -> Bool
== :: DeleteFuotaTask -> DeleteFuotaTask -> Bool
$c== :: DeleteFuotaTask -> DeleteFuotaTask -> Bool
Prelude.Eq, ReadPrec [DeleteFuotaTask]
ReadPrec DeleteFuotaTask
Int -> ReadS DeleteFuotaTask
ReadS [DeleteFuotaTask]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteFuotaTask]
$creadListPrec :: ReadPrec [DeleteFuotaTask]
readPrec :: ReadPrec DeleteFuotaTask
$creadPrec :: ReadPrec DeleteFuotaTask
readList :: ReadS [DeleteFuotaTask]
$creadList :: ReadS [DeleteFuotaTask]
readsPrec :: Int -> ReadS DeleteFuotaTask
$creadsPrec :: Int -> ReadS DeleteFuotaTask
Prelude.Read, Int -> DeleteFuotaTask -> ShowS
[DeleteFuotaTask] -> ShowS
DeleteFuotaTask -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteFuotaTask] -> ShowS
$cshowList :: [DeleteFuotaTask] -> ShowS
show :: DeleteFuotaTask -> String
$cshow :: DeleteFuotaTask -> String
showsPrec :: Int -> DeleteFuotaTask -> ShowS
$cshowsPrec :: Int -> DeleteFuotaTask -> ShowS
Prelude.Show, forall x. Rep DeleteFuotaTask x -> DeleteFuotaTask
forall x. DeleteFuotaTask -> Rep DeleteFuotaTask x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteFuotaTask x -> DeleteFuotaTask
$cfrom :: forall x. DeleteFuotaTask -> Rep DeleteFuotaTask x
Prelude.Generic)

-- |
-- Create a value of 'DeleteFuotaTask' 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:
--
-- 'id', 'deleteFuotaTask_id' - Undocumented member.
newDeleteFuotaTask ::
  -- | 'id'
  Prelude.Text ->
  DeleteFuotaTask
newDeleteFuotaTask :: Text -> DeleteFuotaTask
newDeleteFuotaTask Text
pId_ = DeleteFuotaTask' {$sel:id:DeleteFuotaTask' :: Text
id = Text
pId_}

-- | Undocumented member.
deleteFuotaTask_id :: Lens.Lens' DeleteFuotaTask Prelude.Text
deleteFuotaTask_id :: Lens' DeleteFuotaTask Text
deleteFuotaTask_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteFuotaTask' {Text
id :: Text
$sel:id:DeleteFuotaTask' :: DeleteFuotaTask -> Text
id} -> Text
id) (\s :: DeleteFuotaTask
s@DeleteFuotaTask' {} Text
a -> DeleteFuotaTask
s {$sel:id:DeleteFuotaTask' :: Text
id = Text
a} :: DeleteFuotaTask)

instance Core.AWSRequest DeleteFuotaTask where
  type
    AWSResponse DeleteFuotaTask =
      DeleteFuotaTaskResponse
  request :: (Service -> Service) -> DeleteFuotaTask -> Request DeleteFuotaTask
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 DeleteFuotaTask
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteFuotaTask)))
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 -> DeleteFuotaTaskResponse
DeleteFuotaTaskResponse'
            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 DeleteFuotaTask where
  hashWithSalt :: Int -> DeleteFuotaTask -> Int
hashWithSalt Int
_salt DeleteFuotaTask' {Text
id :: Text
$sel:id:DeleteFuotaTask' :: DeleteFuotaTask -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id

instance Prelude.NFData DeleteFuotaTask where
  rnf :: DeleteFuotaTask -> ()
rnf DeleteFuotaTask' {Text
id :: Text
$sel:id:DeleteFuotaTask' :: DeleteFuotaTask -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
id

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

instance Data.ToPath DeleteFuotaTask where
  toPath :: DeleteFuotaTask -> ByteString
toPath DeleteFuotaTask' {Text
id :: Text
$sel:id:DeleteFuotaTask' :: DeleteFuotaTask -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/fuota-tasks/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
id]

instance Data.ToQuery DeleteFuotaTask where
  toQuery :: DeleteFuotaTask -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newDeleteFuotaTaskResponse' smart constructor.
data DeleteFuotaTaskResponse = DeleteFuotaTaskResponse'
  { -- | The response's http status code.
    DeleteFuotaTaskResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteFuotaTaskResponse -> DeleteFuotaTaskResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteFuotaTaskResponse -> DeleteFuotaTaskResponse -> Bool
$c/= :: DeleteFuotaTaskResponse -> DeleteFuotaTaskResponse -> Bool
== :: DeleteFuotaTaskResponse -> DeleteFuotaTaskResponse -> Bool
$c== :: DeleteFuotaTaskResponse -> DeleteFuotaTaskResponse -> Bool
Prelude.Eq, ReadPrec [DeleteFuotaTaskResponse]
ReadPrec DeleteFuotaTaskResponse
Int -> ReadS DeleteFuotaTaskResponse
ReadS [DeleteFuotaTaskResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteFuotaTaskResponse]
$creadListPrec :: ReadPrec [DeleteFuotaTaskResponse]
readPrec :: ReadPrec DeleteFuotaTaskResponse
$creadPrec :: ReadPrec DeleteFuotaTaskResponse
readList :: ReadS [DeleteFuotaTaskResponse]
$creadList :: ReadS [DeleteFuotaTaskResponse]
readsPrec :: Int -> ReadS DeleteFuotaTaskResponse
$creadsPrec :: Int -> ReadS DeleteFuotaTaskResponse
Prelude.Read, Int -> DeleteFuotaTaskResponse -> ShowS
[DeleteFuotaTaskResponse] -> ShowS
DeleteFuotaTaskResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteFuotaTaskResponse] -> ShowS
$cshowList :: [DeleteFuotaTaskResponse] -> ShowS
show :: DeleteFuotaTaskResponse -> String
$cshow :: DeleteFuotaTaskResponse -> String
showsPrec :: Int -> DeleteFuotaTaskResponse -> ShowS
$cshowsPrec :: Int -> DeleteFuotaTaskResponse -> ShowS
Prelude.Show, forall x. Rep DeleteFuotaTaskResponse x -> DeleteFuotaTaskResponse
forall x. DeleteFuotaTaskResponse -> Rep DeleteFuotaTaskResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteFuotaTaskResponse x -> DeleteFuotaTaskResponse
$cfrom :: forall x. DeleteFuotaTaskResponse -> Rep DeleteFuotaTaskResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteFuotaTaskResponse' 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:
--
-- 'httpStatus', 'deleteFuotaTaskResponse_httpStatus' - The response's http status code.
newDeleteFuotaTaskResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteFuotaTaskResponse
newDeleteFuotaTaskResponse :: Int -> DeleteFuotaTaskResponse
newDeleteFuotaTaskResponse Int
pHttpStatus_ =
  DeleteFuotaTaskResponse' {$sel:httpStatus:DeleteFuotaTaskResponse' :: Int
httpStatus = Int
pHttpStatus_}

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

instance Prelude.NFData DeleteFuotaTaskResponse where
  rnf :: DeleteFuotaTaskResponse -> ()
rnf DeleteFuotaTaskResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteFuotaTaskResponse' :: DeleteFuotaTaskResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus