{-# 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.Transfer.DeleteAccess
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Allows you to delete the access specified in the @ServerID@ and
-- @ExternalID@ parameters.
module Amazonka.Transfer.DeleteAccess
  ( -- * Creating a Request
    DeleteAccess (..),
    newDeleteAccess,

    -- * Request Lenses
    deleteAccess_serverId,
    deleteAccess_externalId,

    -- * Destructuring the Response
    DeleteAccessResponse (..),
    newDeleteAccessResponse,
  )
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.Transfer.Types

-- | /See:/ 'newDeleteAccess' smart constructor.
data DeleteAccess = DeleteAccess'
  { -- | A system-assigned unique identifier for a server that has this user
    -- assigned.
    DeleteAccess -> Text
serverId :: Prelude.Text,
    -- | A unique identifier that is required to identify specific groups within
    -- your directory. The users of the group that you associate have access to
    -- your Amazon S3 or Amazon EFS resources over the enabled protocols using
    -- Transfer Family. If you know the group name, you can view the SID values
    -- by running the following command using Windows PowerShell.
    --
    -- @Get-ADGroup -Filter {samAccountName -like \"@/@YourGroupName@/@*\"} -Properties * | Select SamAccountName,ObjectSid@
    --
    -- In that command, replace /YourGroupName/ with the name of your Active
    -- Directory group.
    --
    -- The regular expression used to validate this parameter is a string of
    -- characters consisting of uppercase and lowercase alphanumeric characters
    -- with no spaces. You can also include underscores or any of the following
    -- characters: =,.\@:\/-
    DeleteAccess -> Text
externalId :: Prelude.Text
  }
  deriving (DeleteAccess -> DeleteAccess -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteAccess -> DeleteAccess -> Bool
$c/= :: DeleteAccess -> DeleteAccess -> Bool
== :: DeleteAccess -> DeleteAccess -> Bool
$c== :: DeleteAccess -> DeleteAccess -> Bool
Prelude.Eq, ReadPrec [DeleteAccess]
ReadPrec DeleteAccess
Int -> ReadS DeleteAccess
ReadS [DeleteAccess]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteAccess]
$creadListPrec :: ReadPrec [DeleteAccess]
readPrec :: ReadPrec DeleteAccess
$creadPrec :: ReadPrec DeleteAccess
readList :: ReadS [DeleteAccess]
$creadList :: ReadS [DeleteAccess]
readsPrec :: Int -> ReadS DeleteAccess
$creadsPrec :: Int -> ReadS DeleteAccess
Prelude.Read, Int -> DeleteAccess -> ShowS
[DeleteAccess] -> ShowS
DeleteAccess -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteAccess] -> ShowS
$cshowList :: [DeleteAccess] -> ShowS
show :: DeleteAccess -> String
$cshow :: DeleteAccess -> String
showsPrec :: Int -> DeleteAccess -> ShowS
$cshowsPrec :: Int -> DeleteAccess -> ShowS
Prelude.Show, forall x. Rep DeleteAccess x -> DeleteAccess
forall x. DeleteAccess -> Rep DeleteAccess x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteAccess x -> DeleteAccess
$cfrom :: forall x. DeleteAccess -> Rep DeleteAccess x
Prelude.Generic)

-- |
-- Create a value of 'DeleteAccess' 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:
--
-- 'serverId', 'deleteAccess_serverId' - A system-assigned unique identifier for a server that has this user
-- assigned.
--
-- 'externalId', 'deleteAccess_externalId' - A unique identifier that is required to identify specific groups within
-- your directory. The users of the group that you associate have access to
-- your Amazon S3 or Amazon EFS resources over the enabled protocols using
-- Transfer Family. If you know the group name, you can view the SID values
-- by running the following command using Windows PowerShell.
--
-- @Get-ADGroup -Filter {samAccountName -like \"@/@YourGroupName@/@*\"} -Properties * | Select SamAccountName,ObjectSid@
--
-- In that command, replace /YourGroupName/ with the name of your Active
-- Directory group.
--
-- The regular expression used to validate this parameter is a string of
-- characters consisting of uppercase and lowercase alphanumeric characters
-- with no spaces. You can also include underscores or any of the following
-- characters: =,.\@:\/-
newDeleteAccess ::
  -- | 'serverId'
  Prelude.Text ->
  -- | 'externalId'
  Prelude.Text ->
  DeleteAccess
newDeleteAccess :: Text -> Text -> DeleteAccess
newDeleteAccess Text
pServerId_ Text
pExternalId_ =
  DeleteAccess'
    { $sel:serverId:DeleteAccess' :: Text
serverId = Text
pServerId_,
      $sel:externalId:DeleteAccess' :: Text
externalId = Text
pExternalId_
    }

-- | A system-assigned unique identifier for a server that has this user
-- assigned.
deleteAccess_serverId :: Lens.Lens' DeleteAccess Prelude.Text
deleteAccess_serverId :: Lens' DeleteAccess Text
deleteAccess_serverId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteAccess' {Text
serverId :: Text
$sel:serverId:DeleteAccess' :: DeleteAccess -> Text
serverId} -> Text
serverId) (\s :: DeleteAccess
s@DeleteAccess' {} Text
a -> DeleteAccess
s {$sel:serverId:DeleteAccess' :: Text
serverId = Text
a} :: DeleteAccess)

-- | A unique identifier that is required to identify specific groups within
-- your directory. The users of the group that you associate have access to
-- your Amazon S3 or Amazon EFS resources over the enabled protocols using
-- Transfer Family. If you know the group name, you can view the SID values
-- by running the following command using Windows PowerShell.
--
-- @Get-ADGroup -Filter {samAccountName -like \"@/@YourGroupName@/@*\"} -Properties * | Select SamAccountName,ObjectSid@
--
-- In that command, replace /YourGroupName/ with the name of your Active
-- Directory group.
--
-- The regular expression used to validate this parameter is a string of
-- characters consisting of uppercase and lowercase alphanumeric characters
-- with no spaces. You can also include underscores or any of the following
-- characters: =,.\@:\/-
deleteAccess_externalId :: Lens.Lens' DeleteAccess Prelude.Text
deleteAccess_externalId :: Lens' DeleteAccess Text
deleteAccess_externalId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteAccess' {Text
externalId :: Text
$sel:externalId:DeleteAccess' :: DeleteAccess -> Text
externalId} -> Text
externalId) (\s :: DeleteAccess
s@DeleteAccess' {} Text
a -> DeleteAccess
s {$sel:externalId:DeleteAccess' :: Text
externalId = Text
a} :: DeleteAccess)

instance Core.AWSRequest DeleteAccess where
  type AWSResponse DeleteAccess = DeleteAccessResponse
  request :: (Service -> Service) -> DeleteAccess -> Request DeleteAccess
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 DeleteAccess
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteAccess)))
response = forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull DeleteAccessResponse
DeleteAccessResponse'

instance Prelude.Hashable DeleteAccess where
  hashWithSalt :: Int -> DeleteAccess -> Int
hashWithSalt Int
_salt DeleteAccess' {Text
externalId :: Text
serverId :: Text
$sel:externalId:DeleteAccess' :: DeleteAccess -> Text
$sel:serverId:DeleteAccess' :: DeleteAccess -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
serverId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
externalId

instance Prelude.NFData DeleteAccess where
  rnf :: DeleteAccess -> ()
rnf DeleteAccess' {Text
externalId :: Text
serverId :: Text
$sel:externalId:DeleteAccess' :: DeleteAccess -> Text
$sel:serverId:DeleteAccess' :: DeleteAccess -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
serverId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
externalId

instance Data.ToHeaders DeleteAccess where
  toHeaders :: DeleteAccess -> [Header]
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 -> [Header]
Data.=# ( ByteString
"TransferService.DeleteAccess" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DeleteAccess where
  toJSON :: DeleteAccess -> Value
toJSON DeleteAccess' {Text
externalId :: Text
serverId :: Text
$sel:externalId:DeleteAccess' :: DeleteAccess -> Text
$sel:serverId:DeleteAccess' :: DeleteAccess -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"ServerId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
serverId),
            forall a. a -> Maybe a
Prelude.Just (Key
"ExternalId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
externalId)
          ]
      )

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

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

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

-- |
-- Create a value of 'DeleteAccessResponse' 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.
newDeleteAccessResponse ::
  DeleteAccessResponse
newDeleteAccessResponse :: DeleteAccessResponse
newDeleteAccessResponse = DeleteAccessResponse
DeleteAccessResponse'

instance Prelude.NFData DeleteAccessResponse where
  rnf :: DeleteAccessResponse -> ()
rnf DeleteAccessResponse
_ = ()