{-# 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.CreateLensShare
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Create a lens share.
--
-- The owner of a lens can share it with other Amazon Web Services
-- accounts, IAM users, an organization, and organizational units (OUs) in
-- the same Amazon Web Services Region. Shared access to a lens is not
-- removed until the lens invitation is deleted.
--
-- __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.CreateLensShare
  ( -- * Creating a Request
    CreateLensShare (..),
    newCreateLensShare,

    -- * Request Lenses
    createLensShare_lensAlias,
    createLensShare_sharedWith,
    createLensShare_clientRequestToken,

    -- * Destructuring the Response
    CreateLensShareResponse (..),
    newCreateLensShareResponse,

    -- * Response Lenses
    createLensShareResponse_shareId,
    createLensShareResponse_httpStatus,
  )
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:/ 'newCreateLensShare' smart constructor.
data CreateLensShare = CreateLensShare'
  { CreateLensShare -> Text
lensAlias :: Prelude.Text,
    CreateLensShare -> Text
sharedWith :: Prelude.Text,
    CreateLensShare -> Text
clientRequestToken :: Prelude.Text
  }
  deriving (CreateLensShare -> CreateLensShare -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateLensShare -> CreateLensShare -> Bool
$c/= :: CreateLensShare -> CreateLensShare -> Bool
== :: CreateLensShare -> CreateLensShare -> Bool
$c== :: CreateLensShare -> CreateLensShare -> Bool
Prelude.Eq, ReadPrec [CreateLensShare]
ReadPrec CreateLensShare
Int -> ReadS CreateLensShare
ReadS [CreateLensShare]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateLensShare]
$creadListPrec :: ReadPrec [CreateLensShare]
readPrec :: ReadPrec CreateLensShare
$creadPrec :: ReadPrec CreateLensShare
readList :: ReadS [CreateLensShare]
$creadList :: ReadS [CreateLensShare]
readsPrec :: Int -> ReadS CreateLensShare
$creadsPrec :: Int -> ReadS CreateLensShare
Prelude.Read, Int -> CreateLensShare -> ShowS
[CreateLensShare] -> ShowS
CreateLensShare -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateLensShare] -> ShowS
$cshowList :: [CreateLensShare] -> ShowS
show :: CreateLensShare -> String
$cshow :: CreateLensShare -> String
showsPrec :: Int -> CreateLensShare -> ShowS
$cshowsPrec :: Int -> CreateLensShare -> ShowS
Prelude.Show, forall x. Rep CreateLensShare x -> CreateLensShare
forall x. CreateLensShare -> Rep CreateLensShare x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateLensShare x -> CreateLensShare
$cfrom :: forall x. CreateLensShare -> Rep CreateLensShare x
Prelude.Generic)

-- |
-- Create a value of 'CreateLensShare' 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:
--
-- 'lensAlias', 'createLensShare_lensAlias' - Undocumented member.
--
-- 'sharedWith', 'createLensShare_sharedWith' - Undocumented member.
--
-- 'clientRequestToken', 'createLensShare_clientRequestToken' - Undocumented member.
newCreateLensShare ::
  -- | 'lensAlias'
  Prelude.Text ->
  -- | 'sharedWith'
  Prelude.Text ->
  -- | 'clientRequestToken'
  Prelude.Text ->
  CreateLensShare
newCreateLensShare :: Text -> Text -> Text -> CreateLensShare
newCreateLensShare
  Text
pLensAlias_
  Text
pSharedWith_
  Text
pClientRequestToken_ =
    CreateLensShare'
      { $sel:lensAlias:CreateLensShare' :: Text
lensAlias = Text
pLensAlias_,
        $sel:sharedWith:CreateLensShare' :: Text
sharedWith = Text
pSharedWith_,
        $sel:clientRequestToken:CreateLensShare' :: Text
clientRequestToken = Text
pClientRequestToken_
      }

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

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

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

instance Core.AWSRequest CreateLensShare where
  type
    AWSResponse CreateLensShare =
      CreateLensShareResponse
  request :: (Service -> Service) -> CreateLensShare -> Request CreateLensShare
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 CreateLensShare
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateLensShare)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text -> Int -> CreateLensShareResponse
CreateLensShareResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ShareId")
            forall (f :: * -> *) a b. Applicative f => 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 CreateLensShare where
  hashWithSalt :: Int -> CreateLensShare -> Int
hashWithSalt Int
_salt CreateLensShare' {Text
clientRequestToken :: Text
sharedWith :: Text
lensAlias :: Text
$sel:clientRequestToken:CreateLensShare' :: CreateLensShare -> Text
$sel:sharedWith:CreateLensShare' :: CreateLensShare -> Text
$sel:lensAlias:CreateLensShare' :: CreateLensShare -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
lensAlias
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
sharedWith
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clientRequestToken

instance Prelude.NFData CreateLensShare where
  rnf :: CreateLensShare -> ()
rnf CreateLensShare' {Text
clientRequestToken :: Text
sharedWith :: Text
lensAlias :: Text
$sel:clientRequestToken:CreateLensShare' :: CreateLensShare -> Text
$sel:sharedWith:CreateLensShare' :: CreateLensShare -> Text
$sel:lensAlias:CreateLensShare' :: CreateLensShare -> Text
..} =
    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
sharedWith
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
clientRequestToken

instance Data.ToHeaders CreateLensShare where
  toHeaders :: CreateLensShare -> ResponseHeaders
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 -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON CreateLensShare where
  toJSON :: CreateLensShare -> Value
toJSON CreateLensShare' {Text
clientRequestToken :: Text
sharedWith :: Text
lensAlias :: Text
$sel:clientRequestToken:CreateLensShare' :: CreateLensShare -> Text
$sel:sharedWith:CreateLensShare' :: CreateLensShare -> Text
$sel:lensAlias:CreateLensShare' :: CreateLensShare -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"SharedWith" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
sharedWith),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"ClientRequestToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
clientRequestToken)
          ]
      )

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

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

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

-- |
-- Create a value of 'CreateLensShareResponse' 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', 'createLensShareResponse_shareId' - Undocumented member.
--
-- 'httpStatus', 'createLensShareResponse_httpStatus' - The response's http status code.
newCreateLensShareResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateLensShareResponse
newCreateLensShareResponse :: Int -> CreateLensShareResponse
newCreateLensShareResponse Int
pHttpStatus_ =
  CreateLensShareResponse'
    { $sel:shareId:CreateLensShareResponse' :: Maybe Text
shareId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateLensShareResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

instance Prelude.NFData CreateLensShareResponse where
  rnf :: CreateLensShareResponse -> ()
rnf CreateLensShareResponse' {Int
Maybe Text
httpStatus :: Int
shareId :: Maybe Text
$sel:httpStatus:CreateLensShareResponse' :: CreateLensShareResponse -> Int
$sel:shareId:CreateLensShareResponse' :: CreateLensShareResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
shareId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus