{-# 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.DataSync.DeleteLocation
-- 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 configuration of a location used by DataSync.
module Amazonka.DataSync.DeleteLocation
  ( -- * Creating a Request
    DeleteLocation (..),
    newDeleteLocation,

    -- * Request Lenses
    deleteLocation_locationArn,

    -- * Destructuring the Response
    DeleteLocationResponse (..),
    newDeleteLocationResponse,

    -- * Response Lenses
    deleteLocationResponse_httpStatus,
  )
where

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

-- | DeleteLocation
--
-- /See:/ 'newDeleteLocation' smart constructor.
data DeleteLocation = DeleteLocation'
  { -- | The Amazon Resource Name (ARN) of the location to delete.
    DeleteLocation -> Text
locationArn :: Prelude.Text
  }
  deriving (DeleteLocation -> DeleteLocation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteLocation -> DeleteLocation -> Bool
$c/= :: DeleteLocation -> DeleteLocation -> Bool
== :: DeleteLocation -> DeleteLocation -> Bool
$c== :: DeleteLocation -> DeleteLocation -> Bool
Prelude.Eq, ReadPrec [DeleteLocation]
ReadPrec DeleteLocation
Int -> ReadS DeleteLocation
ReadS [DeleteLocation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteLocation]
$creadListPrec :: ReadPrec [DeleteLocation]
readPrec :: ReadPrec DeleteLocation
$creadPrec :: ReadPrec DeleteLocation
readList :: ReadS [DeleteLocation]
$creadList :: ReadS [DeleteLocation]
readsPrec :: Int -> ReadS DeleteLocation
$creadsPrec :: Int -> ReadS DeleteLocation
Prelude.Read, Int -> DeleteLocation -> ShowS
[DeleteLocation] -> ShowS
DeleteLocation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteLocation] -> ShowS
$cshowList :: [DeleteLocation] -> ShowS
show :: DeleteLocation -> String
$cshow :: DeleteLocation -> String
showsPrec :: Int -> DeleteLocation -> ShowS
$cshowsPrec :: Int -> DeleteLocation -> ShowS
Prelude.Show, forall x. Rep DeleteLocation x -> DeleteLocation
forall x. DeleteLocation -> Rep DeleteLocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteLocation x -> DeleteLocation
$cfrom :: forall x. DeleteLocation -> Rep DeleteLocation x
Prelude.Generic)

-- |
-- Create a value of 'DeleteLocation' 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:
--
-- 'locationArn', 'deleteLocation_locationArn' - The Amazon Resource Name (ARN) of the location to delete.
newDeleteLocation ::
  -- | 'locationArn'
  Prelude.Text ->
  DeleteLocation
newDeleteLocation :: Text -> DeleteLocation
newDeleteLocation Text
pLocationArn_ =
  DeleteLocation' {$sel:locationArn:DeleteLocation' :: Text
locationArn = Text
pLocationArn_}

-- | The Amazon Resource Name (ARN) of the location to delete.
deleteLocation_locationArn :: Lens.Lens' DeleteLocation Prelude.Text
deleteLocation_locationArn :: Lens' DeleteLocation Text
deleteLocation_locationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteLocation' {Text
locationArn :: Text
$sel:locationArn:DeleteLocation' :: DeleteLocation -> Text
locationArn} -> Text
locationArn) (\s :: DeleteLocation
s@DeleteLocation' {} Text
a -> DeleteLocation
s {$sel:locationArn:DeleteLocation' :: Text
locationArn = Text
a} :: DeleteLocation)

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

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

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

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

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

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

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

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

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