{-# 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.EFS.DeleteFileSystemPolicy
-- 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 @FileSystemPolicy@ for the specified file system. The
-- default @FileSystemPolicy@ goes into effect once the existing policy is
-- deleted. For more information about the default file system policy, see
-- <https://docs.aws.amazon.com/efs/latest/ug/res-based-policies-efs.html Using Resource-based Policies with EFS>.
--
-- This operation requires permissions for the
-- @elasticfilesystem:DeleteFileSystemPolicy@ action.
module Amazonka.EFS.DeleteFileSystemPolicy
  ( -- * Creating a Request
    DeleteFileSystemPolicy (..),
    newDeleteFileSystemPolicy,

    -- * Request Lenses
    deleteFileSystemPolicy_fileSystemId,

    -- * Destructuring the Response
    DeleteFileSystemPolicyResponse (..),
    newDeleteFileSystemPolicyResponse,
  )
where

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

-- | /See:/ 'newDeleteFileSystemPolicy' smart constructor.
data DeleteFileSystemPolicy = DeleteFileSystemPolicy'
  { -- | Specifies the EFS file system for which to delete the
    -- @FileSystemPolicy@.
    DeleteFileSystemPolicy -> Text
fileSystemId :: Prelude.Text
  }
  deriving (DeleteFileSystemPolicy -> DeleteFileSystemPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteFileSystemPolicy -> DeleteFileSystemPolicy -> Bool
$c/= :: DeleteFileSystemPolicy -> DeleteFileSystemPolicy -> Bool
== :: DeleteFileSystemPolicy -> DeleteFileSystemPolicy -> Bool
$c== :: DeleteFileSystemPolicy -> DeleteFileSystemPolicy -> Bool
Prelude.Eq, ReadPrec [DeleteFileSystemPolicy]
ReadPrec DeleteFileSystemPolicy
Int -> ReadS DeleteFileSystemPolicy
ReadS [DeleteFileSystemPolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteFileSystemPolicy]
$creadListPrec :: ReadPrec [DeleteFileSystemPolicy]
readPrec :: ReadPrec DeleteFileSystemPolicy
$creadPrec :: ReadPrec DeleteFileSystemPolicy
readList :: ReadS [DeleteFileSystemPolicy]
$creadList :: ReadS [DeleteFileSystemPolicy]
readsPrec :: Int -> ReadS DeleteFileSystemPolicy
$creadsPrec :: Int -> ReadS DeleteFileSystemPolicy
Prelude.Read, Int -> DeleteFileSystemPolicy -> ShowS
[DeleteFileSystemPolicy] -> ShowS
DeleteFileSystemPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteFileSystemPolicy] -> ShowS
$cshowList :: [DeleteFileSystemPolicy] -> ShowS
show :: DeleteFileSystemPolicy -> String
$cshow :: DeleteFileSystemPolicy -> String
showsPrec :: Int -> DeleteFileSystemPolicy -> ShowS
$cshowsPrec :: Int -> DeleteFileSystemPolicy -> ShowS
Prelude.Show, forall x. Rep DeleteFileSystemPolicy x -> DeleteFileSystemPolicy
forall x. DeleteFileSystemPolicy -> Rep DeleteFileSystemPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteFileSystemPolicy x -> DeleteFileSystemPolicy
$cfrom :: forall x. DeleteFileSystemPolicy -> Rep DeleteFileSystemPolicy x
Prelude.Generic)

-- |
-- Create a value of 'DeleteFileSystemPolicy' 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:
--
-- 'fileSystemId', 'deleteFileSystemPolicy_fileSystemId' - Specifies the EFS file system for which to delete the
-- @FileSystemPolicy@.
newDeleteFileSystemPolicy ::
  -- | 'fileSystemId'
  Prelude.Text ->
  DeleteFileSystemPolicy
newDeleteFileSystemPolicy :: Text -> DeleteFileSystemPolicy
newDeleteFileSystemPolicy Text
pFileSystemId_ =
  DeleteFileSystemPolicy'
    { $sel:fileSystemId:DeleteFileSystemPolicy' :: Text
fileSystemId =
        Text
pFileSystemId_
    }

-- | Specifies the EFS file system for which to delete the
-- @FileSystemPolicy@.
deleteFileSystemPolicy_fileSystemId :: Lens.Lens' DeleteFileSystemPolicy Prelude.Text
deleteFileSystemPolicy_fileSystemId :: Lens' DeleteFileSystemPolicy Text
deleteFileSystemPolicy_fileSystemId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteFileSystemPolicy' {Text
fileSystemId :: Text
$sel:fileSystemId:DeleteFileSystemPolicy' :: DeleteFileSystemPolicy -> Text
fileSystemId} -> Text
fileSystemId) (\s :: DeleteFileSystemPolicy
s@DeleteFileSystemPolicy' {} Text
a -> DeleteFileSystemPolicy
s {$sel:fileSystemId:DeleteFileSystemPolicy' :: Text
fileSystemId = Text
a} :: DeleteFileSystemPolicy)

instance Core.AWSRequest DeleteFileSystemPolicy where
  type
    AWSResponse DeleteFileSystemPolicy =
      DeleteFileSystemPolicyResponse
  request :: (Service -> Service)
-> DeleteFileSystemPolicy -> Request DeleteFileSystemPolicy
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteFileSystemPolicy
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteFileSystemPolicy)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull
      DeleteFileSystemPolicyResponse
DeleteFileSystemPolicyResponse'

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

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

instance Data.ToHeaders DeleteFileSystemPolicy where
  toHeaders :: DeleteFileSystemPolicy -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath DeleteFileSystemPolicy where
  toPath :: DeleteFileSystemPolicy -> ByteString
toPath DeleteFileSystemPolicy' {Text
fileSystemId :: Text
$sel:fileSystemId:DeleteFileSystemPolicy' :: DeleteFileSystemPolicy -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/2015-02-01/file-systems/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
fileSystemId,
        ByteString
"/policy"
      ]

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

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

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

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