{-# 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.MediaStore.DeleteContainerPolicy
-- 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 access policy that is associated with the specified
-- container.
module Amazonka.MediaStore.DeleteContainerPolicy
  ( -- * Creating a Request
    DeleteContainerPolicy (..),
    newDeleteContainerPolicy,

    -- * Request Lenses
    deleteContainerPolicy_containerName,

    -- * Destructuring the Response
    DeleteContainerPolicyResponse (..),
    newDeleteContainerPolicyResponse,

    -- * Response Lenses
    deleteContainerPolicyResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDeleteContainerPolicy' smart constructor.
data DeleteContainerPolicy = DeleteContainerPolicy'
  { -- | The name of the container that holds the policy.
    DeleteContainerPolicy -> Text
containerName :: Prelude.Text
  }
  deriving (DeleteContainerPolicy -> DeleteContainerPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteContainerPolicy -> DeleteContainerPolicy -> Bool
$c/= :: DeleteContainerPolicy -> DeleteContainerPolicy -> Bool
== :: DeleteContainerPolicy -> DeleteContainerPolicy -> Bool
$c== :: DeleteContainerPolicy -> DeleteContainerPolicy -> Bool
Prelude.Eq, ReadPrec [DeleteContainerPolicy]
ReadPrec DeleteContainerPolicy
Int -> ReadS DeleteContainerPolicy
ReadS [DeleteContainerPolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteContainerPolicy]
$creadListPrec :: ReadPrec [DeleteContainerPolicy]
readPrec :: ReadPrec DeleteContainerPolicy
$creadPrec :: ReadPrec DeleteContainerPolicy
readList :: ReadS [DeleteContainerPolicy]
$creadList :: ReadS [DeleteContainerPolicy]
readsPrec :: Int -> ReadS DeleteContainerPolicy
$creadsPrec :: Int -> ReadS DeleteContainerPolicy
Prelude.Read, Int -> DeleteContainerPolicy -> ShowS
[DeleteContainerPolicy] -> ShowS
DeleteContainerPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteContainerPolicy] -> ShowS
$cshowList :: [DeleteContainerPolicy] -> ShowS
show :: DeleteContainerPolicy -> String
$cshow :: DeleteContainerPolicy -> String
showsPrec :: Int -> DeleteContainerPolicy -> ShowS
$cshowsPrec :: Int -> DeleteContainerPolicy -> ShowS
Prelude.Show, forall x. Rep DeleteContainerPolicy x -> DeleteContainerPolicy
forall x. DeleteContainerPolicy -> Rep DeleteContainerPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteContainerPolicy x -> DeleteContainerPolicy
$cfrom :: forall x. DeleteContainerPolicy -> Rep DeleteContainerPolicy x
Prelude.Generic)

-- |
-- Create a value of 'DeleteContainerPolicy' 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:
--
-- 'containerName', 'deleteContainerPolicy_containerName' - The name of the container that holds the policy.
newDeleteContainerPolicy ::
  -- | 'containerName'
  Prelude.Text ->
  DeleteContainerPolicy
newDeleteContainerPolicy :: Text -> DeleteContainerPolicy
newDeleteContainerPolicy Text
pContainerName_ =
  DeleteContainerPolicy'
    { $sel:containerName:DeleteContainerPolicy' :: Text
containerName =
        Text
pContainerName_
    }

-- | The name of the container that holds the policy.
deleteContainerPolicy_containerName :: Lens.Lens' DeleteContainerPolicy Prelude.Text
deleteContainerPolicy_containerName :: Lens' DeleteContainerPolicy Text
deleteContainerPolicy_containerName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteContainerPolicy' {Text
containerName :: Text
$sel:containerName:DeleteContainerPolicy' :: DeleteContainerPolicy -> Text
containerName} -> Text
containerName) (\s :: DeleteContainerPolicy
s@DeleteContainerPolicy' {} Text
a -> DeleteContainerPolicy
s {$sel:containerName:DeleteContainerPolicy' :: Text
containerName = Text
a} :: DeleteContainerPolicy)

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

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

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

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

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

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

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

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

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