{-# 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.WorkMail.DeleteResource
-- 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 resource.
module Amazonka.WorkMail.DeleteResource
  ( -- * Creating a Request
    DeleteResource (..),
    newDeleteResource,

    -- * Request Lenses
    deleteResource_organizationId,
    deleteResource_resourceId,

    -- * Destructuring the Response
    DeleteResourceResponse (..),
    newDeleteResourceResponse,

    -- * Response Lenses
    deleteResourceResponse_httpStatus,
  )
where

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
import Amazonka.WorkMail.Types

-- | /See:/ 'newDeleteResource' smart constructor.
data DeleteResource = DeleteResource'
  { -- | The identifier associated with the organization from which the resource
    -- is deleted.
    DeleteResource -> Text
organizationId :: Prelude.Text,
    -- | The identifier of the resource to be deleted.
    DeleteResource -> Text
resourceId :: Prelude.Text
  }
  deriving (DeleteResource -> DeleteResource -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteResource -> DeleteResource -> Bool
$c/= :: DeleteResource -> DeleteResource -> Bool
== :: DeleteResource -> DeleteResource -> Bool
$c== :: DeleteResource -> DeleteResource -> Bool
Prelude.Eq, ReadPrec [DeleteResource]
ReadPrec DeleteResource
Int -> ReadS DeleteResource
ReadS [DeleteResource]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteResource]
$creadListPrec :: ReadPrec [DeleteResource]
readPrec :: ReadPrec DeleteResource
$creadPrec :: ReadPrec DeleteResource
readList :: ReadS [DeleteResource]
$creadList :: ReadS [DeleteResource]
readsPrec :: Int -> ReadS DeleteResource
$creadsPrec :: Int -> ReadS DeleteResource
Prelude.Read, Int -> DeleteResource -> ShowS
[DeleteResource] -> ShowS
DeleteResource -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteResource] -> ShowS
$cshowList :: [DeleteResource] -> ShowS
show :: DeleteResource -> String
$cshow :: DeleteResource -> String
showsPrec :: Int -> DeleteResource -> ShowS
$cshowsPrec :: Int -> DeleteResource -> ShowS
Prelude.Show, forall x. Rep DeleteResource x -> DeleteResource
forall x. DeleteResource -> Rep DeleteResource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteResource x -> DeleteResource
$cfrom :: forall x. DeleteResource -> Rep DeleteResource x
Prelude.Generic)

-- |
-- Create a value of 'DeleteResource' 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:
--
-- 'organizationId', 'deleteResource_organizationId' - The identifier associated with the organization from which the resource
-- is deleted.
--
-- 'resourceId', 'deleteResource_resourceId' - The identifier of the resource to be deleted.
newDeleteResource ::
  -- | 'organizationId'
  Prelude.Text ->
  -- | 'resourceId'
  Prelude.Text ->
  DeleteResource
newDeleteResource :: Text -> Text -> DeleteResource
newDeleteResource Text
pOrganizationId_ Text
pResourceId_ =
  DeleteResource'
    { $sel:organizationId:DeleteResource' :: Text
organizationId = Text
pOrganizationId_,
      $sel:resourceId:DeleteResource' :: Text
resourceId = Text
pResourceId_
    }

-- | The identifier associated with the organization from which the resource
-- is deleted.
deleteResource_organizationId :: Lens.Lens' DeleteResource Prelude.Text
deleteResource_organizationId :: Lens' DeleteResource Text
deleteResource_organizationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteResource' {Text
organizationId :: Text
$sel:organizationId:DeleteResource' :: DeleteResource -> Text
organizationId} -> Text
organizationId) (\s :: DeleteResource
s@DeleteResource' {} Text
a -> DeleteResource
s {$sel:organizationId:DeleteResource' :: Text
organizationId = Text
a} :: DeleteResource)

-- | The identifier of the resource to be deleted.
deleteResource_resourceId :: Lens.Lens' DeleteResource Prelude.Text
deleteResource_resourceId :: Lens' DeleteResource Text
deleteResource_resourceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteResource' {Text
resourceId :: Text
$sel:resourceId:DeleteResource' :: DeleteResource -> Text
resourceId} -> Text
resourceId) (\s :: DeleteResource
s@DeleteResource' {} Text
a -> DeleteResource
s {$sel:resourceId:DeleteResource' :: Text
resourceId = Text
a} :: DeleteResource)

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

instance Prelude.NFData DeleteResource where
  rnf :: DeleteResource -> ()
rnf DeleteResource' {Text
resourceId :: Text
organizationId :: Text
$sel:resourceId:DeleteResource' :: DeleteResource -> Text
$sel:organizationId:DeleteResource' :: DeleteResource -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
organizationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
resourceId

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

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

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

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

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

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

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