{-# 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.NetworkManager.DeleteDevice
-- 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 an existing device. You must first disassociate the device from
-- any links and customer gateways.
module Amazonka.NetworkManager.DeleteDevice
  ( -- * Creating a Request
    DeleteDevice (..),
    newDeleteDevice,

    -- * Request Lenses
    deleteDevice_globalNetworkId,
    deleteDevice_deviceId,

    -- * Destructuring the Response
    DeleteDeviceResponse (..),
    newDeleteDeviceResponse,

    -- * Response Lenses
    deleteDeviceResponse_device,
    deleteDeviceResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDeleteDevice' smart constructor.
data DeleteDevice = DeleteDevice'
  { -- | The ID of the global network.
    DeleteDevice -> Text
globalNetworkId :: Prelude.Text,
    -- | The ID of the device.
    DeleteDevice -> Text
deviceId :: Prelude.Text
  }
  deriving (DeleteDevice -> DeleteDevice -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteDevice -> DeleteDevice -> Bool
$c/= :: DeleteDevice -> DeleteDevice -> Bool
== :: DeleteDevice -> DeleteDevice -> Bool
$c== :: DeleteDevice -> DeleteDevice -> Bool
Prelude.Eq, ReadPrec [DeleteDevice]
ReadPrec DeleteDevice
Int -> ReadS DeleteDevice
ReadS [DeleteDevice]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteDevice]
$creadListPrec :: ReadPrec [DeleteDevice]
readPrec :: ReadPrec DeleteDevice
$creadPrec :: ReadPrec DeleteDevice
readList :: ReadS [DeleteDevice]
$creadList :: ReadS [DeleteDevice]
readsPrec :: Int -> ReadS DeleteDevice
$creadsPrec :: Int -> ReadS DeleteDevice
Prelude.Read, Int -> DeleteDevice -> ShowS
[DeleteDevice] -> ShowS
DeleteDevice -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteDevice] -> ShowS
$cshowList :: [DeleteDevice] -> ShowS
show :: DeleteDevice -> String
$cshow :: DeleteDevice -> String
showsPrec :: Int -> DeleteDevice -> ShowS
$cshowsPrec :: Int -> DeleteDevice -> ShowS
Prelude.Show, forall x. Rep DeleteDevice x -> DeleteDevice
forall x. DeleteDevice -> Rep DeleteDevice x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteDevice x -> DeleteDevice
$cfrom :: forall x. DeleteDevice -> Rep DeleteDevice x
Prelude.Generic)

-- |
-- Create a value of 'DeleteDevice' 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:
--
-- 'globalNetworkId', 'deleteDevice_globalNetworkId' - The ID of the global network.
--
-- 'deviceId', 'deleteDevice_deviceId' - The ID of the device.
newDeleteDevice ::
  -- | 'globalNetworkId'
  Prelude.Text ->
  -- | 'deviceId'
  Prelude.Text ->
  DeleteDevice
newDeleteDevice :: Text -> Text -> DeleteDevice
newDeleteDevice Text
pGlobalNetworkId_ Text
pDeviceId_ =
  DeleteDevice'
    { $sel:globalNetworkId:DeleteDevice' :: Text
globalNetworkId = Text
pGlobalNetworkId_,
      $sel:deviceId:DeleteDevice' :: Text
deviceId = Text
pDeviceId_
    }

-- | The ID of the global network.
deleteDevice_globalNetworkId :: Lens.Lens' DeleteDevice Prelude.Text
deleteDevice_globalNetworkId :: Lens' DeleteDevice Text
deleteDevice_globalNetworkId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteDevice' {Text
globalNetworkId :: Text
$sel:globalNetworkId:DeleteDevice' :: DeleteDevice -> Text
globalNetworkId} -> Text
globalNetworkId) (\s :: DeleteDevice
s@DeleteDevice' {} Text
a -> DeleteDevice
s {$sel:globalNetworkId:DeleteDevice' :: Text
globalNetworkId = Text
a} :: DeleteDevice)

-- | The ID of the device.
deleteDevice_deviceId :: Lens.Lens' DeleteDevice Prelude.Text
deleteDevice_deviceId :: Lens' DeleteDevice Text
deleteDevice_deviceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteDevice' {Text
deviceId :: Text
$sel:deviceId:DeleteDevice' :: DeleteDevice -> Text
deviceId} -> Text
deviceId) (\s :: DeleteDevice
s@DeleteDevice' {} Text
a -> DeleteDevice
s {$sel:deviceId:DeleteDevice' :: Text
deviceId = Text
a} :: DeleteDevice)

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

instance Prelude.NFData DeleteDevice where
  rnf :: DeleteDevice -> ()
rnf DeleteDevice' {Text
deviceId :: Text
globalNetworkId :: Text
$sel:deviceId:DeleteDevice' :: DeleteDevice -> Text
$sel:globalNetworkId:DeleteDevice' :: DeleteDevice -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
globalNetworkId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
deviceId

instance Data.ToHeaders DeleteDevice where
  toHeaders :: DeleteDevice -> 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 DeleteDevice where
  toPath :: DeleteDevice -> ByteString
toPath DeleteDevice' {Text
deviceId :: Text
globalNetworkId :: Text
$sel:deviceId:DeleteDevice' :: DeleteDevice -> Text
$sel:globalNetworkId:DeleteDevice' :: DeleteDevice -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/global-networks/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
globalNetworkId,
        ByteString
"/devices/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
deviceId
      ]

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

-- | /See:/ 'newDeleteDeviceResponse' smart constructor.
data DeleteDeviceResponse = DeleteDeviceResponse'
  { -- | Information about the device.
    DeleteDeviceResponse -> Maybe Device
device :: Prelude.Maybe Device,
    -- | The response's http status code.
    DeleteDeviceResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteDeviceResponse -> DeleteDeviceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteDeviceResponse -> DeleteDeviceResponse -> Bool
$c/= :: DeleteDeviceResponse -> DeleteDeviceResponse -> Bool
== :: DeleteDeviceResponse -> DeleteDeviceResponse -> Bool
$c== :: DeleteDeviceResponse -> DeleteDeviceResponse -> Bool
Prelude.Eq, Int -> DeleteDeviceResponse -> ShowS
[DeleteDeviceResponse] -> ShowS
DeleteDeviceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteDeviceResponse] -> ShowS
$cshowList :: [DeleteDeviceResponse] -> ShowS
show :: DeleteDeviceResponse -> String
$cshow :: DeleteDeviceResponse -> String
showsPrec :: Int -> DeleteDeviceResponse -> ShowS
$cshowsPrec :: Int -> DeleteDeviceResponse -> ShowS
Prelude.Show, forall x. Rep DeleteDeviceResponse x -> DeleteDeviceResponse
forall x. DeleteDeviceResponse -> Rep DeleteDeviceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteDeviceResponse x -> DeleteDeviceResponse
$cfrom :: forall x. DeleteDeviceResponse -> Rep DeleteDeviceResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteDeviceResponse' 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:
--
-- 'device', 'deleteDeviceResponse_device' - Information about the device.
--
-- 'httpStatus', 'deleteDeviceResponse_httpStatus' - The response's http status code.
newDeleteDeviceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteDeviceResponse
newDeleteDeviceResponse :: Int -> DeleteDeviceResponse
newDeleteDeviceResponse Int
pHttpStatus_ =
  DeleteDeviceResponse'
    { $sel:device:DeleteDeviceResponse' :: Maybe Device
device = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteDeviceResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the device.
deleteDeviceResponse_device :: Lens.Lens' DeleteDeviceResponse (Prelude.Maybe Device)
deleteDeviceResponse_device :: Lens' DeleteDeviceResponse (Maybe Device)
deleteDeviceResponse_device = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteDeviceResponse' {Maybe Device
device :: Maybe Device
$sel:device:DeleteDeviceResponse' :: DeleteDeviceResponse -> Maybe Device
device} -> Maybe Device
device) (\s :: DeleteDeviceResponse
s@DeleteDeviceResponse' {} Maybe Device
a -> DeleteDeviceResponse
s {$sel:device:DeleteDeviceResponse' :: Maybe Device
device = Maybe Device
a} :: DeleteDeviceResponse)

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

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