{-# 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.Lightsail.DeleteDomainEntry
-- 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 specific domain entry.
--
-- The @delete domain entry@ operation supports tag-based access control
-- via resource tags applied to the resource identified by @domain name@.
-- For more information, see the
-- <https://lightsail.aws.amazon.com/ls/docs/en_us/articles/amazon-lightsail-controlling-access-using-tags Amazon Lightsail Developer Guide>.
module Amazonka.Lightsail.DeleteDomainEntry
  ( -- * Creating a Request
    DeleteDomainEntry (..),
    newDeleteDomainEntry,

    -- * Request Lenses
    deleteDomainEntry_domainName,
    deleteDomainEntry_domainEntry,

    -- * Destructuring the Response
    DeleteDomainEntryResponse (..),
    newDeleteDomainEntryResponse,

    -- * Response Lenses
    deleteDomainEntryResponse_operation,
    deleteDomainEntryResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDeleteDomainEntry' smart constructor.
data DeleteDomainEntry = DeleteDomainEntry'
  { -- | The name of the domain entry to delete.
    DeleteDomainEntry -> Text
domainName :: Prelude.Text,
    -- | An array of key-value pairs containing information about your domain
    -- entries.
    DeleteDomainEntry -> DomainEntry
domainEntry :: DomainEntry
  }
  deriving (DeleteDomainEntry -> DeleteDomainEntry -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteDomainEntry -> DeleteDomainEntry -> Bool
$c/= :: DeleteDomainEntry -> DeleteDomainEntry -> Bool
== :: DeleteDomainEntry -> DeleteDomainEntry -> Bool
$c== :: DeleteDomainEntry -> DeleteDomainEntry -> Bool
Prelude.Eq, ReadPrec [DeleteDomainEntry]
ReadPrec DeleteDomainEntry
Int -> ReadS DeleteDomainEntry
ReadS [DeleteDomainEntry]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteDomainEntry]
$creadListPrec :: ReadPrec [DeleteDomainEntry]
readPrec :: ReadPrec DeleteDomainEntry
$creadPrec :: ReadPrec DeleteDomainEntry
readList :: ReadS [DeleteDomainEntry]
$creadList :: ReadS [DeleteDomainEntry]
readsPrec :: Int -> ReadS DeleteDomainEntry
$creadsPrec :: Int -> ReadS DeleteDomainEntry
Prelude.Read, Int -> DeleteDomainEntry -> ShowS
[DeleteDomainEntry] -> ShowS
DeleteDomainEntry -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteDomainEntry] -> ShowS
$cshowList :: [DeleteDomainEntry] -> ShowS
show :: DeleteDomainEntry -> String
$cshow :: DeleteDomainEntry -> String
showsPrec :: Int -> DeleteDomainEntry -> ShowS
$cshowsPrec :: Int -> DeleteDomainEntry -> ShowS
Prelude.Show, forall x. Rep DeleteDomainEntry x -> DeleteDomainEntry
forall x. DeleteDomainEntry -> Rep DeleteDomainEntry x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteDomainEntry x -> DeleteDomainEntry
$cfrom :: forall x. DeleteDomainEntry -> Rep DeleteDomainEntry x
Prelude.Generic)

-- |
-- Create a value of 'DeleteDomainEntry' 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:
--
-- 'domainName', 'deleteDomainEntry_domainName' - The name of the domain entry to delete.
--
-- 'domainEntry', 'deleteDomainEntry_domainEntry' - An array of key-value pairs containing information about your domain
-- entries.
newDeleteDomainEntry ::
  -- | 'domainName'
  Prelude.Text ->
  -- | 'domainEntry'
  DomainEntry ->
  DeleteDomainEntry
newDeleteDomainEntry :: Text -> DomainEntry -> DeleteDomainEntry
newDeleteDomainEntry Text
pDomainName_ DomainEntry
pDomainEntry_ =
  DeleteDomainEntry'
    { $sel:domainName:DeleteDomainEntry' :: Text
domainName = Text
pDomainName_,
      $sel:domainEntry:DeleteDomainEntry' :: DomainEntry
domainEntry = DomainEntry
pDomainEntry_
    }

-- | The name of the domain entry to delete.
deleteDomainEntry_domainName :: Lens.Lens' DeleteDomainEntry Prelude.Text
deleteDomainEntry_domainName :: Lens' DeleteDomainEntry Text
deleteDomainEntry_domainName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteDomainEntry' {Text
domainName :: Text
$sel:domainName:DeleteDomainEntry' :: DeleteDomainEntry -> Text
domainName} -> Text
domainName) (\s :: DeleteDomainEntry
s@DeleteDomainEntry' {} Text
a -> DeleteDomainEntry
s {$sel:domainName:DeleteDomainEntry' :: Text
domainName = Text
a} :: DeleteDomainEntry)

-- | An array of key-value pairs containing information about your domain
-- entries.
deleteDomainEntry_domainEntry :: Lens.Lens' DeleteDomainEntry DomainEntry
deleteDomainEntry_domainEntry :: Lens' DeleteDomainEntry DomainEntry
deleteDomainEntry_domainEntry = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteDomainEntry' {DomainEntry
domainEntry :: DomainEntry
$sel:domainEntry:DeleteDomainEntry' :: DeleteDomainEntry -> DomainEntry
domainEntry} -> DomainEntry
domainEntry) (\s :: DeleteDomainEntry
s@DeleteDomainEntry' {} DomainEntry
a -> DeleteDomainEntry
s {$sel:domainEntry:DeleteDomainEntry' :: DomainEntry
domainEntry = DomainEntry
a} :: DeleteDomainEntry)

instance Core.AWSRequest DeleteDomainEntry where
  type
    AWSResponse DeleteDomainEntry =
      DeleteDomainEntryResponse
  request :: (Service -> Service)
-> DeleteDomainEntry -> Request DeleteDomainEntry
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 DeleteDomainEntry
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteDomainEntry)))
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 Operation -> Int -> DeleteDomainEntryResponse
DeleteDomainEntryResponse'
            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
"operation")
            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 DeleteDomainEntry where
  hashWithSalt :: Int -> DeleteDomainEntry -> Int
hashWithSalt Int
_salt DeleteDomainEntry' {Text
DomainEntry
domainEntry :: DomainEntry
domainName :: Text
$sel:domainEntry:DeleteDomainEntry' :: DeleteDomainEntry -> DomainEntry
$sel:domainName:DeleteDomainEntry' :: DeleteDomainEntry -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
domainName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` DomainEntry
domainEntry

instance Prelude.NFData DeleteDomainEntry where
  rnf :: DeleteDomainEntry -> ()
rnf DeleteDomainEntry' {Text
DomainEntry
domainEntry :: DomainEntry
domainName :: Text
$sel:domainEntry:DeleteDomainEntry' :: DeleteDomainEntry -> DomainEntry
$sel:domainName:DeleteDomainEntry' :: DeleteDomainEntry -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
domainName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf DomainEntry
domainEntry

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

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

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

-- | /See:/ 'newDeleteDomainEntryResponse' smart constructor.
data DeleteDomainEntryResponse = DeleteDomainEntryResponse'
  { -- | An array of objects that describe the result of the action, such as the
    -- status of the request, the timestamp of the request, and the resources
    -- affected by the request.
    DeleteDomainEntryResponse -> Maybe Operation
operation :: Prelude.Maybe Operation,
    -- | The response's http status code.
    DeleteDomainEntryResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteDomainEntryResponse -> DeleteDomainEntryResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteDomainEntryResponse -> DeleteDomainEntryResponse -> Bool
$c/= :: DeleteDomainEntryResponse -> DeleteDomainEntryResponse -> Bool
== :: DeleteDomainEntryResponse -> DeleteDomainEntryResponse -> Bool
$c== :: DeleteDomainEntryResponse -> DeleteDomainEntryResponse -> Bool
Prelude.Eq, ReadPrec [DeleteDomainEntryResponse]
ReadPrec DeleteDomainEntryResponse
Int -> ReadS DeleteDomainEntryResponse
ReadS [DeleteDomainEntryResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteDomainEntryResponse]
$creadListPrec :: ReadPrec [DeleteDomainEntryResponse]
readPrec :: ReadPrec DeleteDomainEntryResponse
$creadPrec :: ReadPrec DeleteDomainEntryResponse
readList :: ReadS [DeleteDomainEntryResponse]
$creadList :: ReadS [DeleteDomainEntryResponse]
readsPrec :: Int -> ReadS DeleteDomainEntryResponse
$creadsPrec :: Int -> ReadS DeleteDomainEntryResponse
Prelude.Read, Int -> DeleteDomainEntryResponse -> ShowS
[DeleteDomainEntryResponse] -> ShowS
DeleteDomainEntryResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteDomainEntryResponse] -> ShowS
$cshowList :: [DeleteDomainEntryResponse] -> ShowS
show :: DeleteDomainEntryResponse -> String
$cshow :: DeleteDomainEntryResponse -> String
showsPrec :: Int -> DeleteDomainEntryResponse -> ShowS
$cshowsPrec :: Int -> DeleteDomainEntryResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteDomainEntryResponse x -> DeleteDomainEntryResponse
forall x.
DeleteDomainEntryResponse -> Rep DeleteDomainEntryResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteDomainEntryResponse x -> DeleteDomainEntryResponse
$cfrom :: forall x.
DeleteDomainEntryResponse -> Rep DeleteDomainEntryResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteDomainEntryResponse' 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:
--
-- 'operation', 'deleteDomainEntryResponse_operation' - An array of objects that describe the result of the action, such as the
-- status of the request, the timestamp of the request, and the resources
-- affected by the request.
--
-- 'httpStatus', 'deleteDomainEntryResponse_httpStatus' - The response's http status code.
newDeleteDomainEntryResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteDomainEntryResponse
newDeleteDomainEntryResponse :: Int -> DeleteDomainEntryResponse
newDeleteDomainEntryResponse Int
pHttpStatus_ =
  DeleteDomainEntryResponse'
    { $sel:operation:DeleteDomainEntryResponse' :: Maybe Operation
operation =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteDomainEntryResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array of objects that describe the result of the action, such as the
-- status of the request, the timestamp of the request, and the resources
-- affected by the request.
deleteDomainEntryResponse_operation :: Lens.Lens' DeleteDomainEntryResponse (Prelude.Maybe Operation)
deleteDomainEntryResponse_operation :: Lens' DeleteDomainEntryResponse (Maybe Operation)
deleteDomainEntryResponse_operation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteDomainEntryResponse' {Maybe Operation
operation :: Maybe Operation
$sel:operation:DeleteDomainEntryResponse' :: DeleteDomainEntryResponse -> Maybe Operation
operation} -> Maybe Operation
operation) (\s :: DeleteDomainEntryResponse
s@DeleteDomainEntryResponse' {} Maybe Operation
a -> DeleteDomainEntryResponse
s {$sel:operation:DeleteDomainEntryResponse' :: Maybe Operation
operation = Maybe Operation
a} :: DeleteDomainEntryResponse)

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

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