{-# 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.WellArchitected.DeleteLensShare
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Delete a lens share.
--
-- After the lens share is deleted, Amazon Web Services accounts, IAM
-- users, organizations, and organizational units (OUs) that you shared the
-- lens with can continue to use it, but they will no longer be able to
-- apply it to new workloads.
--
-- __Disclaimer__
--
-- By sharing your custom lenses with other Amazon Web Services accounts,
-- you acknowledge that Amazon Web Services will make your custom lenses
-- available to those other accounts. Those other accounts may continue to
-- access and use your shared custom lenses even if you delete the custom
-- lenses from your own Amazon Web Services account or terminate your
-- Amazon Web Services account.
module Amazonka.WellArchitected.DeleteLensShare
  ( -- * Creating a Request
    DeleteLensShare (..),
    newDeleteLensShare,

    -- * Request Lenses
    deleteLensShare_shareId,
    deleteLensShare_lensAlias,
    deleteLensShare_clientRequestToken,

    -- * Destructuring the Response
    DeleteLensShareResponse (..),
    newDeleteLensShareResponse,
  )
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.WellArchitected.Types

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

-- |
-- Create a value of 'DeleteLensShare' 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:
--
-- 'shareId', 'deleteLensShare_shareId' - Undocumented member.
--
-- 'lensAlias', 'deleteLensShare_lensAlias' - Undocumented member.
--
-- 'clientRequestToken', 'deleteLensShare_clientRequestToken' - Undocumented member.
newDeleteLensShare ::
  -- | 'shareId'
  Prelude.Text ->
  -- | 'lensAlias'
  Prelude.Text ->
  -- | 'clientRequestToken'
  Prelude.Text ->
  DeleteLensShare
newDeleteLensShare :: Text -> Text -> Text -> DeleteLensShare
newDeleteLensShare
  Text
pShareId_
  Text
pLensAlias_
  Text
pClientRequestToken_ =
    DeleteLensShare'
      { $sel:shareId:DeleteLensShare' :: Text
shareId = Text
pShareId_,
        $sel:lensAlias:DeleteLensShare' :: Text
lensAlias = Text
pLensAlias_,
        $sel:clientRequestToken:DeleteLensShare' :: Text
clientRequestToken = Text
pClientRequestToken_
      }

-- | Undocumented member.
deleteLensShare_shareId :: Lens.Lens' DeleteLensShare Prelude.Text
deleteLensShare_shareId :: Lens' DeleteLensShare Text
deleteLensShare_shareId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteLensShare' {Text
shareId :: Text
$sel:shareId:DeleteLensShare' :: DeleteLensShare -> Text
shareId} -> Text
shareId) (\s :: DeleteLensShare
s@DeleteLensShare' {} Text
a -> DeleteLensShare
s {$sel:shareId:DeleteLensShare' :: Text
shareId = Text
a} :: DeleteLensShare)

-- | Undocumented member.
deleteLensShare_lensAlias :: Lens.Lens' DeleteLensShare Prelude.Text
deleteLensShare_lensAlias :: Lens' DeleteLensShare Text
deleteLensShare_lensAlias = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteLensShare' {Text
lensAlias :: Text
$sel:lensAlias:DeleteLensShare' :: DeleteLensShare -> Text
lensAlias} -> Text
lensAlias) (\s :: DeleteLensShare
s@DeleteLensShare' {} Text
a -> DeleteLensShare
s {$sel:lensAlias:DeleteLensShare' :: Text
lensAlias = Text
a} :: DeleteLensShare)

-- | Undocumented member.
deleteLensShare_clientRequestToken :: Lens.Lens' DeleteLensShare Prelude.Text
deleteLensShare_clientRequestToken :: Lens' DeleteLensShare Text
deleteLensShare_clientRequestToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteLensShare' {Text
clientRequestToken :: Text
$sel:clientRequestToken:DeleteLensShare' :: DeleteLensShare -> Text
clientRequestToken} -> Text
clientRequestToken) (\s :: DeleteLensShare
s@DeleteLensShare' {} Text
a -> DeleteLensShare
s {$sel:clientRequestToken:DeleteLensShare' :: Text
clientRequestToken = Text
a} :: DeleteLensShare)

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

instance Prelude.Hashable DeleteLensShare where
  hashWithSalt :: Int -> DeleteLensShare -> Int
hashWithSalt Int
_salt DeleteLensShare' {Text
clientRequestToken :: Text
lensAlias :: Text
shareId :: Text
$sel:clientRequestToken:DeleteLensShare' :: DeleteLensShare -> Text
$sel:lensAlias:DeleteLensShare' :: DeleteLensShare -> Text
$sel:shareId:DeleteLensShare' :: DeleteLensShare -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
shareId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
lensAlias
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clientRequestToken

instance Prelude.NFData DeleteLensShare where
  rnf :: DeleteLensShare -> ()
rnf DeleteLensShare' {Text
clientRequestToken :: Text
lensAlias :: Text
shareId :: Text
$sel:clientRequestToken:DeleteLensShare' :: DeleteLensShare -> Text
$sel:lensAlias:DeleteLensShare' :: DeleteLensShare -> Text
$sel:shareId:DeleteLensShare' :: DeleteLensShare -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
shareId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
lensAlias
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
clientRequestToken

instance Data.ToHeaders DeleteLensShare where
  toHeaders :: DeleteLensShare -> [Header]
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath DeleteLensShare where
  toPath :: DeleteLensShare -> ByteString
toPath DeleteLensShare' {Text
clientRequestToken :: Text
lensAlias :: Text
shareId :: Text
$sel:clientRequestToken:DeleteLensShare' :: DeleteLensShare -> Text
$sel:lensAlias:DeleteLensShare' :: DeleteLensShare -> Text
$sel:shareId:DeleteLensShare' :: DeleteLensShare -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/lenses/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
lensAlias,
        ByteString
"/shares/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
shareId
      ]

instance Data.ToQuery DeleteLensShare where
  toQuery :: DeleteLensShare -> QueryString
toQuery DeleteLensShare' {Text
clientRequestToken :: Text
lensAlias :: Text
shareId :: Text
$sel:clientRequestToken:DeleteLensShare' :: DeleteLensShare -> Text
$sel:lensAlias:DeleteLensShare' :: DeleteLensShare -> Text
$sel:shareId:DeleteLensShare' :: DeleteLensShare -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"ClientRequestToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
clientRequestToken]

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

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

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