{-# 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.AlexaBusiness.DeleteNetworkProfile
-- 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 network profile by the network profile ARN.
module Amazonka.AlexaBusiness.DeleteNetworkProfile
  ( -- * Creating a Request
    DeleteNetworkProfile (..),
    newDeleteNetworkProfile,

    -- * Request Lenses
    deleteNetworkProfile_networkProfileArn,

    -- * Destructuring the Response
    DeleteNetworkProfileResponse (..),
    newDeleteNetworkProfileResponse,

    -- * Response Lenses
    deleteNetworkProfileResponse_httpStatus,
  )
where

import Amazonka.AlexaBusiness.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

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

-- |
-- Create a value of 'DeleteNetworkProfile' 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:
--
-- 'networkProfileArn', 'deleteNetworkProfile_networkProfileArn' - The ARN of the network profile associated with a device.
newDeleteNetworkProfile ::
  -- | 'networkProfileArn'
  Prelude.Text ->
  DeleteNetworkProfile
newDeleteNetworkProfile :: Text -> DeleteNetworkProfile
newDeleteNetworkProfile Text
pNetworkProfileArn_ =
  DeleteNetworkProfile'
    { $sel:networkProfileArn:DeleteNetworkProfile' :: Text
networkProfileArn =
        Text
pNetworkProfileArn_
    }

-- | The ARN of the network profile associated with a device.
deleteNetworkProfile_networkProfileArn :: Lens.Lens' DeleteNetworkProfile Prelude.Text
deleteNetworkProfile_networkProfileArn :: Lens' DeleteNetworkProfile Text
deleteNetworkProfile_networkProfileArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteNetworkProfile' {Text
networkProfileArn :: Text
$sel:networkProfileArn:DeleteNetworkProfile' :: DeleteNetworkProfile -> Text
networkProfileArn} -> Text
networkProfileArn) (\s :: DeleteNetworkProfile
s@DeleteNetworkProfile' {} Text
a -> DeleteNetworkProfile
s {$sel:networkProfileArn:DeleteNetworkProfile' :: Text
networkProfileArn = Text
a} :: DeleteNetworkProfile)

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

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

instance Data.ToHeaders DeleteNetworkProfile where
  toHeaders :: DeleteNetworkProfile -> 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
"AlexaForBusiness.DeleteNetworkProfile" ::
                          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 DeleteNetworkProfile where
  toJSON :: DeleteNetworkProfile -> Value
toJSON DeleteNetworkProfile' {Text
networkProfileArn :: Text
$sel:networkProfileArn:DeleteNetworkProfile' :: DeleteNetworkProfile -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"NetworkProfileArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
networkProfileArn)
          ]
      )

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

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

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

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

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

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