{-# 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.IoTSiteWise.DeleteDashboard
-- 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 dashboard from IoT SiteWise Monitor.
module Amazonka.IoTSiteWise.DeleteDashboard
  ( -- * Creating a Request
    DeleteDashboard (..),
    newDeleteDashboard,

    -- * Request Lenses
    deleteDashboard_clientToken,
    deleteDashboard_dashboardId,

    -- * Destructuring the Response
    DeleteDashboardResponse (..),
    newDeleteDashboardResponse,

    -- * Response Lenses
    deleteDashboardResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDeleteDashboard' smart constructor.
data DeleteDashboard = DeleteDashboard'
  { -- | A unique case-sensitive identifier that you can provide to ensure the
    -- idempotency of the request. Don\'t reuse this client token if a new
    -- idempotent request is required.
    DeleteDashboard -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | The ID of the dashboard to delete.
    DeleteDashboard -> Text
dashboardId :: Prelude.Text
  }
  deriving (DeleteDashboard -> DeleteDashboard -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteDashboard -> DeleteDashboard -> Bool
$c/= :: DeleteDashboard -> DeleteDashboard -> Bool
== :: DeleteDashboard -> DeleteDashboard -> Bool
$c== :: DeleteDashboard -> DeleteDashboard -> Bool
Prelude.Eq, ReadPrec [DeleteDashboard]
ReadPrec DeleteDashboard
Int -> ReadS DeleteDashboard
ReadS [DeleteDashboard]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteDashboard]
$creadListPrec :: ReadPrec [DeleteDashboard]
readPrec :: ReadPrec DeleteDashboard
$creadPrec :: ReadPrec DeleteDashboard
readList :: ReadS [DeleteDashboard]
$creadList :: ReadS [DeleteDashboard]
readsPrec :: Int -> ReadS DeleteDashboard
$creadsPrec :: Int -> ReadS DeleteDashboard
Prelude.Read, Int -> DeleteDashboard -> ShowS
[DeleteDashboard] -> ShowS
DeleteDashboard -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteDashboard] -> ShowS
$cshowList :: [DeleteDashboard] -> ShowS
show :: DeleteDashboard -> String
$cshow :: DeleteDashboard -> String
showsPrec :: Int -> DeleteDashboard -> ShowS
$cshowsPrec :: Int -> DeleteDashboard -> ShowS
Prelude.Show, forall x. Rep DeleteDashboard x -> DeleteDashboard
forall x. DeleteDashboard -> Rep DeleteDashboard x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteDashboard x -> DeleteDashboard
$cfrom :: forall x. DeleteDashboard -> Rep DeleteDashboard x
Prelude.Generic)

-- |
-- Create a value of 'DeleteDashboard' 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:
--
-- 'clientToken', 'deleteDashboard_clientToken' - A unique case-sensitive identifier that you can provide to ensure the
-- idempotency of the request. Don\'t reuse this client token if a new
-- idempotent request is required.
--
-- 'dashboardId', 'deleteDashboard_dashboardId' - The ID of the dashboard to delete.
newDeleteDashboard ::
  -- | 'dashboardId'
  Prelude.Text ->
  DeleteDashboard
newDeleteDashboard :: Text -> DeleteDashboard
newDeleteDashboard Text
pDashboardId_ =
  DeleteDashboard'
    { $sel:clientToken:DeleteDashboard' :: Maybe Text
clientToken = forall a. Maybe a
Prelude.Nothing,
      $sel:dashboardId:DeleteDashboard' :: Text
dashboardId = Text
pDashboardId_
    }

-- | A unique case-sensitive identifier that you can provide to ensure the
-- idempotency of the request. Don\'t reuse this client token if a new
-- idempotent request is required.
deleteDashboard_clientToken :: Lens.Lens' DeleteDashboard (Prelude.Maybe Prelude.Text)
deleteDashboard_clientToken :: Lens' DeleteDashboard (Maybe Text)
deleteDashboard_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteDashboard' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:DeleteDashboard' :: DeleteDashboard -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: DeleteDashboard
s@DeleteDashboard' {} Maybe Text
a -> DeleteDashboard
s {$sel:clientToken:DeleteDashboard' :: Maybe Text
clientToken = Maybe Text
a} :: DeleteDashboard)

-- | The ID of the dashboard to delete.
deleteDashboard_dashboardId :: Lens.Lens' DeleteDashboard Prelude.Text
deleteDashboard_dashboardId :: Lens' DeleteDashboard Text
deleteDashboard_dashboardId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteDashboard' {Text
dashboardId :: Text
$sel:dashboardId:DeleteDashboard' :: DeleteDashboard -> Text
dashboardId} -> Text
dashboardId) (\s :: DeleteDashboard
s@DeleteDashboard' {} Text
a -> DeleteDashboard
s {$sel:dashboardId:DeleteDashboard' :: Text
dashboardId = Text
a} :: DeleteDashboard)

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

instance Prelude.NFData DeleteDashboard where
  rnf :: DeleteDashboard -> ()
rnf DeleteDashboard' {Maybe Text
Text
dashboardId :: Text
clientToken :: Maybe Text
$sel:dashboardId:DeleteDashboard' :: DeleteDashboard -> Text
$sel:clientToken:DeleteDashboard' :: DeleteDashboard -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
dashboardId

instance Data.ToHeaders DeleteDashboard where
  toHeaders :: DeleteDashboard -> ResponseHeaders
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 -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath DeleteDashboard where
  toPath :: DeleteDashboard -> ByteString
toPath DeleteDashboard' {Maybe Text
Text
dashboardId :: Text
clientToken :: Maybe Text
$sel:dashboardId:DeleteDashboard' :: DeleteDashboard -> Text
$sel:clientToken:DeleteDashboard' :: DeleteDashboard -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/dashboards/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
dashboardId]

instance Data.ToQuery DeleteDashboard where
  toQuery :: DeleteDashboard -> QueryString
toQuery DeleteDashboard' {Maybe Text
Text
dashboardId :: Text
clientToken :: Maybe Text
$sel:dashboardId:DeleteDashboard' :: DeleteDashboard -> Text
$sel:clientToken:DeleteDashboard' :: DeleteDashboard -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"clientToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
clientToken]

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

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

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

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