{-# 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.OAM.CreateLink
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a link between a source account and a sink that you have created
-- in a monitoring account.
--
-- Before you create a link, you must create a sink in the monitoring
-- account and create a sink policy in that account. The sink policy must
-- permit the source account to link to it. You can grant permission to
-- source accounts by granting permission to an entire organization or to
-- individual accounts.
--
-- For more information, see
-- <https://docs.aws.amazon.com/OAM/latest/APIReference/API_CreateSink.html CreateSink>
-- and
-- <https://docs.aws.amazon.com/OAM/latest/APIReference/API_PutSinkPolicy.html PutSinkPolicy>.
--
-- Each monitoring account can be linked to as many as 100,000 source
-- accounts.
--
-- Each source account can be linked to as many as five monitoring
-- accounts.
module Amazonka.OAM.CreateLink
  ( -- * Creating a Request
    CreateLink (..),
    newCreateLink,

    -- * Request Lenses
    createLink_tags,
    createLink_labelTemplate,
    createLink_resourceTypes,
    createLink_sinkIdentifier,

    -- * Destructuring the Response
    CreateLinkResponse (..),
    newCreateLinkResponse,

    -- * Response Lenses
    createLinkResponse_arn,
    createLinkResponse_id,
    createLinkResponse_label,
    createLinkResponse_labelTemplate,
    createLinkResponse_resourceTypes,
    createLinkResponse_sinkArn,
    createLinkResponse_tags,
    createLinkResponse_httpStatus,
  )
where

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

-- | /See:/ 'newCreateLink' smart constructor.
data CreateLink = CreateLink'
  { -- | Assigns one or more tags (key-value pairs) to the link.
    --
    -- Tags can help you organize and categorize your resources. You can also
    -- use them to scope user permissions by granting a user permission to
    -- access or change only resources with certain tag values.
    --
    -- For more information about using tags to control access, see
    -- <https://docs.aws.amazon.com/IAM/latest/UserGuide/access_tags.html Controlling access to Amazon Web Services resources using tags>.
    CreateLink -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | Specify a friendly human-readable name to use to identify this source
    -- account when you are viewing data from it in the monitoring account.
    --
    -- You can use a custom label or use the following variables:
    --
    -- -   @$AccountName@ is the name of the account
    --
    -- -   @$AccountEmail@ is the globally unique email address of the account
    --
    -- -   @$AccountEmailNoDomain@ is the email address of the account without
    --     the domain name
    CreateLink -> Text
labelTemplate :: Prelude.Text,
    -- | An array of strings that define which types of data that the source
    -- account shares with the monitoring account.
    CreateLink -> NonEmpty ResourceType
resourceTypes :: Prelude.NonEmpty ResourceType,
    -- | The ARN of the sink to use to create this link. You can use
    -- <https://docs.aws.amazon.com/OAM/latest/APIReference/API_ListSinks.html ListSinks>
    -- to find the ARNs of sinks.
    --
    -- For more information about sinks, see
    -- <https://docs.aws.amazon.com/OAM/latest/APIReference/API_CreateSink.html CreateSink>.
    CreateLink -> Text
sinkIdentifier :: Prelude.Text
  }
  deriving (CreateLink -> CreateLink -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateLink -> CreateLink -> Bool
$c/= :: CreateLink -> CreateLink -> Bool
== :: CreateLink -> CreateLink -> Bool
$c== :: CreateLink -> CreateLink -> Bool
Prelude.Eq, ReadPrec [CreateLink]
ReadPrec CreateLink
Int -> ReadS CreateLink
ReadS [CreateLink]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateLink]
$creadListPrec :: ReadPrec [CreateLink]
readPrec :: ReadPrec CreateLink
$creadPrec :: ReadPrec CreateLink
readList :: ReadS [CreateLink]
$creadList :: ReadS [CreateLink]
readsPrec :: Int -> ReadS CreateLink
$creadsPrec :: Int -> ReadS CreateLink
Prelude.Read, Int -> CreateLink -> ShowS
[CreateLink] -> ShowS
CreateLink -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateLink] -> ShowS
$cshowList :: [CreateLink] -> ShowS
show :: CreateLink -> String
$cshow :: CreateLink -> String
showsPrec :: Int -> CreateLink -> ShowS
$cshowsPrec :: Int -> CreateLink -> ShowS
Prelude.Show, forall x. Rep CreateLink x -> CreateLink
forall x. CreateLink -> Rep CreateLink x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateLink x -> CreateLink
$cfrom :: forall x. CreateLink -> Rep CreateLink x
Prelude.Generic)

-- |
-- Create a value of 'CreateLink' 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:
--
-- 'tags', 'createLink_tags' - Assigns one or more tags (key-value pairs) to the link.
--
-- Tags can help you organize and categorize your resources. You can also
-- use them to scope user permissions by granting a user permission to
-- access or change only resources with certain tag values.
--
-- For more information about using tags to control access, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/access_tags.html Controlling access to Amazon Web Services resources using tags>.
--
-- 'labelTemplate', 'createLink_labelTemplate' - Specify a friendly human-readable name to use to identify this source
-- account when you are viewing data from it in the monitoring account.
--
-- You can use a custom label or use the following variables:
--
-- -   @$AccountName@ is the name of the account
--
-- -   @$AccountEmail@ is the globally unique email address of the account
--
-- -   @$AccountEmailNoDomain@ is the email address of the account without
--     the domain name
--
-- 'resourceTypes', 'createLink_resourceTypes' - An array of strings that define which types of data that the source
-- account shares with the monitoring account.
--
-- 'sinkIdentifier', 'createLink_sinkIdentifier' - The ARN of the sink to use to create this link. You can use
-- <https://docs.aws.amazon.com/OAM/latest/APIReference/API_ListSinks.html ListSinks>
-- to find the ARNs of sinks.
--
-- For more information about sinks, see
-- <https://docs.aws.amazon.com/OAM/latest/APIReference/API_CreateSink.html CreateSink>.
newCreateLink ::
  -- | 'labelTemplate'
  Prelude.Text ->
  -- | 'resourceTypes'
  Prelude.NonEmpty ResourceType ->
  -- | 'sinkIdentifier'
  Prelude.Text ->
  CreateLink
newCreateLink :: Text -> NonEmpty ResourceType -> Text -> CreateLink
newCreateLink
  Text
pLabelTemplate_
  NonEmpty ResourceType
pResourceTypes_
  Text
pSinkIdentifier_ =
    CreateLink'
      { $sel:tags:CreateLink' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:labelTemplate:CreateLink' :: Text
labelTemplate = Text
pLabelTemplate_,
        $sel:resourceTypes:CreateLink' :: NonEmpty ResourceType
resourceTypes = forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty ResourceType
pResourceTypes_,
        $sel:sinkIdentifier:CreateLink' :: Text
sinkIdentifier = Text
pSinkIdentifier_
      }

-- | Assigns one or more tags (key-value pairs) to the link.
--
-- Tags can help you organize and categorize your resources. You can also
-- use them to scope user permissions by granting a user permission to
-- access or change only resources with certain tag values.
--
-- For more information about using tags to control access, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/access_tags.html Controlling access to Amazon Web Services resources using tags>.
createLink_tags :: Lens.Lens' CreateLink (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createLink_tags :: Lens' CreateLink (Maybe (HashMap Text Text))
createLink_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLink' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateLink' :: CreateLink -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateLink
s@CreateLink' {} Maybe (HashMap Text Text)
a -> CreateLink
s {$sel:tags:CreateLink' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateLink) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | Specify a friendly human-readable name to use to identify this source
-- account when you are viewing data from it in the monitoring account.
--
-- You can use a custom label or use the following variables:
--
-- -   @$AccountName@ is the name of the account
--
-- -   @$AccountEmail@ is the globally unique email address of the account
--
-- -   @$AccountEmailNoDomain@ is the email address of the account without
--     the domain name
createLink_labelTemplate :: Lens.Lens' CreateLink Prelude.Text
createLink_labelTemplate :: Lens' CreateLink Text
createLink_labelTemplate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLink' {Text
labelTemplate :: Text
$sel:labelTemplate:CreateLink' :: CreateLink -> Text
labelTemplate} -> Text
labelTemplate) (\s :: CreateLink
s@CreateLink' {} Text
a -> CreateLink
s {$sel:labelTemplate:CreateLink' :: Text
labelTemplate = Text
a} :: CreateLink)

-- | An array of strings that define which types of data that the source
-- account shares with the monitoring account.
createLink_resourceTypes :: Lens.Lens' CreateLink (Prelude.NonEmpty ResourceType)
createLink_resourceTypes :: Lens' CreateLink (NonEmpty ResourceType)
createLink_resourceTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLink' {NonEmpty ResourceType
resourceTypes :: NonEmpty ResourceType
$sel:resourceTypes:CreateLink' :: CreateLink -> NonEmpty ResourceType
resourceTypes} -> NonEmpty ResourceType
resourceTypes) (\s :: CreateLink
s@CreateLink' {} NonEmpty ResourceType
a -> CreateLink
s {$sel:resourceTypes:CreateLink' :: NonEmpty ResourceType
resourceTypes = NonEmpty ResourceType
a} :: CreateLink) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The ARN of the sink to use to create this link. You can use
-- <https://docs.aws.amazon.com/OAM/latest/APIReference/API_ListSinks.html ListSinks>
-- to find the ARNs of sinks.
--
-- For more information about sinks, see
-- <https://docs.aws.amazon.com/OAM/latest/APIReference/API_CreateSink.html CreateSink>.
createLink_sinkIdentifier :: Lens.Lens' CreateLink Prelude.Text
createLink_sinkIdentifier :: Lens' CreateLink Text
createLink_sinkIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLink' {Text
sinkIdentifier :: Text
$sel:sinkIdentifier:CreateLink' :: CreateLink -> Text
sinkIdentifier} -> Text
sinkIdentifier) (\s :: CreateLink
s@CreateLink' {} Text
a -> CreateLink
s {$sel:sinkIdentifier:CreateLink' :: Text
sinkIdentifier = Text
a} :: CreateLink)

instance Core.AWSRequest CreateLink where
  type AWSResponse CreateLink = CreateLinkResponse
  request :: (Service -> Service) -> CreateLink -> Request CreateLink
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 CreateLink
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateLink)))
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
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Text
-> Maybe (HashMap Text Text)
-> Int
-> CreateLinkResponse
CreateLinkResponse'
            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
"Arn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Id")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Label")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"LabelTemplate")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ResourceTypes" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"SinkArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Tags" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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 CreateLink where
  hashWithSalt :: Int -> CreateLink -> Int
hashWithSalt Int
_salt CreateLink' {Maybe (HashMap Text Text)
NonEmpty ResourceType
Text
sinkIdentifier :: Text
resourceTypes :: NonEmpty ResourceType
labelTemplate :: Text
tags :: Maybe (HashMap Text Text)
$sel:sinkIdentifier:CreateLink' :: CreateLink -> Text
$sel:resourceTypes:CreateLink' :: CreateLink -> NonEmpty ResourceType
$sel:labelTemplate:CreateLink' :: CreateLink -> Text
$sel:tags:CreateLink' :: CreateLink -> Maybe (HashMap Text Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
labelTemplate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty ResourceType
resourceTypes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
sinkIdentifier

instance Prelude.NFData CreateLink where
  rnf :: CreateLink -> ()
rnf CreateLink' {Maybe (HashMap Text Text)
NonEmpty ResourceType
Text
sinkIdentifier :: Text
resourceTypes :: NonEmpty ResourceType
labelTemplate :: Text
tags :: Maybe (HashMap Text Text)
$sel:sinkIdentifier:CreateLink' :: CreateLink -> Text
$sel:resourceTypes:CreateLink' :: CreateLink -> NonEmpty ResourceType
$sel:labelTemplate:CreateLink' :: CreateLink -> Text
$sel:tags:CreateLink' :: CreateLink -> Maybe (HashMap Text Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
labelTemplate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty ResourceType
resourceTypes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
sinkIdentifier

instance Data.ToHeaders CreateLink where
  toHeaders :: CreateLink -> 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 CreateLink where
  toJSON :: CreateLink -> Value
toJSON CreateLink' {Maybe (HashMap Text Text)
NonEmpty ResourceType
Text
sinkIdentifier :: Text
resourceTypes :: NonEmpty ResourceType
labelTemplate :: Text
tags :: Maybe (HashMap Text Text)
$sel:sinkIdentifier:CreateLink' :: CreateLink -> Text
$sel:resourceTypes:CreateLink' :: CreateLink -> NonEmpty ResourceType
$sel:labelTemplate:CreateLink' :: CreateLink -> Text
$sel:tags:CreateLink' :: CreateLink -> Maybe (HashMap Text Text)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Tags" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (HashMap Text Text)
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"LabelTemplate" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
labelTemplate),
            forall a. a -> Maybe a
Prelude.Just (Key
"ResourceTypes" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty ResourceType
resourceTypes),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"SinkIdentifier" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
sinkIdentifier)
          ]
      )

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

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

-- | /See:/ 'newCreateLinkResponse' smart constructor.
data CreateLinkResponse = CreateLinkResponse'
  { -- | The ARN of the link that is newly created.
    CreateLinkResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The random ID string that Amazon Web Services generated as part of the
    -- link ARN.
    CreateLinkResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The label that you assigned to this link. If the @labelTemplate@
    -- includes variables, this field displays the variables resolved to their
    -- actual values.
    CreateLinkResponse -> Maybe Text
label :: Prelude.Maybe Prelude.Text,
    -- | The exact label template that you specified, with the variables not
    -- resolved.
    CreateLinkResponse -> Maybe Text
labelTemplate :: Prelude.Maybe Prelude.Text,
    -- | The resource types supported by this link.
    CreateLinkResponse -> Maybe [Text]
resourceTypes :: Prelude.Maybe [Prelude.Text],
    -- | The ARN of the sink that is used for this link.
    CreateLinkResponse -> Maybe Text
sinkArn :: Prelude.Maybe Prelude.Text,
    -- | The tags assigned to the link.
    CreateLinkResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The response's http status code.
    CreateLinkResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateLinkResponse -> CreateLinkResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateLinkResponse -> CreateLinkResponse -> Bool
$c/= :: CreateLinkResponse -> CreateLinkResponse -> Bool
== :: CreateLinkResponse -> CreateLinkResponse -> Bool
$c== :: CreateLinkResponse -> CreateLinkResponse -> Bool
Prelude.Eq, ReadPrec [CreateLinkResponse]
ReadPrec CreateLinkResponse
Int -> ReadS CreateLinkResponse
ReadS [CreateLinkResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateLinkResponse]
$creadListPrec :: ReadPrec [CreateLinkResponse]
readPrec :: ReadPrec CreateLinkResponse
$creadPrec :: ReadPrec CreateLinkResponse
readList :: ReadS [CreateLinkResponse]
$creadList :: ReadS [CreateLinkResponse]
readsPrec :: Int -> ReadS CreateLinkResponse
$creadsPrec :: Int -> ReadS CreateLinkResponse
Prelude.Read, Int -> CreateLinkResponse -> ShowS
[CreateLinkResponse] -> ShowS
CreateLinkResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateLinkResponse] -> ShowS
$cshowList :: [CreateLinkResponse] -> ShowS
show :: CreateLinkResponse -> String
$cshow :: CreateLinkResponse -> String
showsPrec :: Int -> CreateLinkResponse -> ShowS
$cshowsPrec :: Int -> CreateLinkResponse -> ShowS
Prelude.Show, forall x. Rep CreateLinkResponse x -> CreateLinkResponse
forall x. CreateLinkResponse -> Rep CreateLinkResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateLinkResponse x -> CreateLinkResponse
$cfrom :: forall x. CreateLinkResponse -> Rep CreateLinkResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateLinkResponse' 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:
--
-- 'arn', 'createLinkResponse_arn' - The ARN of the link that is newly created.
--
-- 'id', 'createLinkResponse_id' - The random ID string that Amazon Web Services generated as part of the
-- link ARN.
--
-- 'label', 'createLinkResponse_label' - The label that you assigned to this link. If the @labelTemplate@
-- includes variables, this field displays the variables resolved to their
-- actual values.
--
-- 'labelTemplate', 'createLinkResponse_labelTemplate' - The exact label template that you specified, with the variables not
-- resolved.
--
-- 'resourceTypes', 'createLinkResponse_resourceTypes' - The resource types supported by this link.
--
-- 'sinkArn', 'createLinkResponse_sinkArn' - The ARN of the sink that is used for this link.
--
-- 'tags', 'createLinkResponse_tags' - The tags assigned to the link.
--
-- 'httpStatus', 'createLinkResponse_httpStatus' - The response's http status code.
newCreateLinkResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateLinkResponse
newCreateLinkResponse :: Int -> CreateLinkResponse
newCreateLinkResponse Int
pHttpStatus_ =
  CreateLinkResponse'
    { $sel:arn:CreateLinkResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:id:CreateLinkResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:label:CreateLinkResponse' :: Maybe Text
label = forall a. Maybe a
Prelude.Nothing,
      $sel:labelTemplate:CreateLinkResponse' :: Maybe Text
labelTemplate = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceTypes:CreateLinkResponse' :: Maybe [Text]
resourceTypes = forall a. Maybe a
Prelude.Nothing,
      $sel:sinkArn:CreateLinkResponse' :: Maybe Text
sinkArn = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateLinkResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateLinkResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ARN of the link that is newly created.
createLinkResponse_arn :: Lens.Lens' CreateLinkResponse (Prelude.Maybe Prelude.Text)
createLinkResponse_arn :: Lens' CreateLinkResponse (Maybe Text)
createLinkResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLinkResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:CreateLinkResponse' :: CreateLinkResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: CreateLinkResponse
s@CreateLinkResponse' {} Maybe Text
a -> CreateLinkResponse
s {$sel:arn:CreateLinkResponse' :: Maybe Text
arn = Maybe Text
a} :: CreateLinkResponse)

-- | The random ID string that Amazon Web Services generated as part of the
-- link ARN.
createLinkResponse_id :: Lens.Lens' CreateLinkResponse (Prelude.Maybe Prelude.Text)
createLinkResponse_id :: Lens' CreateLinkResponse (Maybe Text)
createLinkResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLinkResponse' {Maybe Text
id :: Maybe Text
$sel:id:CreateLinkResponse' :: CreateLinkResponse -> Maybe Text
id} -> Maybe Text
id) (\s :: CreateLinkResponse
s@CreateLinkResponse' {} Maybe Text
a -> CreateLinkResponse
s {$sel:id:CreateLinkResponse' :: Maybe Text
id = Maybe Text
a} :: CreateLinkResponse)

-- | The label that you assigned to this link. If the @labelTemplate@
-- includes variables, this field displays the variables resolved to their
-- actual values.
createLinkResponse_label :: Lens.Lens' CreateLinkResponse (Prelude.Maybe Prelude.Text)
createLinkResponse_label :: Lens' CreateLinkResponse (Maybe Text)
createLinkResponse_label = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLinkResponse' {Maybe Text
label :: Maybe Text
$sel:label:CreateLinkResponse' :: CreateLinkResponse -> Maybe Text
label} -> Maybe Text
label) (\s :: CreateLinkResponse
s@CreateLinkResponse' {} Maybe Text
a -> CreateLinkResponse
s {$sel:label:CreateLinkResponse' :: Maybe Text
label = Maybe Text
a} :: CreateLinkResponse)

-- | The exact label template that you specified, with the variables not
-- resolved.
createLinkResponse_labelTemplate :: Lens.Lens' CreateLinkResponse (Prelude.Maybe Prelude.Text)
createLinkResponse_labelTemplate :: Lens' CreateLinkResponse (Maybe Text)
createLinkResponse_labelTemplate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLinkResponse' {Maybe Text
labelTemplate :: Maybe Text
$sel:labelTemplate:CreateLinkResponse' :: CreateLinkResponse -> Maybe Text
labelTemplate} -> Maybe Text
labelTemplate) (\s :: CreateLinkResponse
s@CreateLinkResponse' {} Maybe Text
a -> CreateLinkResponse
s {$sel:labelTemplate:CreateLinkResponse' :: Maybe Text
labelTemplate = Maybe Text
a} :: CreateLinkResponse)

-- | The resource types supported by this link.
createLinkResponse_resourceTypes :: Lens.Lens' CreateLinkResponse (Prelude.Maybe [Prelude.Text])
createLinkResponse_resourceTypes :: Lens' CreateLinkResponse (Maybe [Text])
createLinkResponse_resourceTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLinkResponse' {Maybe [Text]
resourceTypes :: Maybe [Text]
$sel:resourceTypes:CreateLinkResponse' :: CreateLinkResponse -> Maybe [Text]
resourceTypes} -> Maybe [Text]
resourceTypes) (\s :: CreateLinkResponse
s@CreateLinkResponse' {} Maybe [Text]
a -> CreateLinkResponse
s {$sel:resourceTypes:CreateLinkResponse' :: Maybe [Text]
resourceTypes = Maybe [Text]
a} :: CreateLinkResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The ARN of the sink that is used for this link.
createLinkResponse_sinkArn :: Lens.Lens' CreateLinkResponse (Prelude.Maybe Prelude.Text)
createLinkResponse_sinkArn :: Lens' CreateLinkResponse (Maybe Text)
createLinkResponse_sinkArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLinkResponse' {Maybe Text
sinkArn :: Maybe Text
$sel:sinkArn:CreateLinkResponse' :: CreateLinkResponse -> Maybe Text
sinkArn} -> Maybe Text
sinkArn) (\s :: CreateLinkResponse
s@CreateLinkResponse' {} Maybe Text
a -> CreateLinkResponse
s {$sel:sinkArn:CreateLinkResponse' :: Maybe Text
sinkArn = Maybe Text
a} :: CreateLinkResponse)

-- | The tags assigned to the link.
createLinkResponse_tags :: Lens.Lens' CreateLinkResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createLinkResponse_tags :: Lens' CreateLinkResponse (Maybe (HashMap Text Text))
createLinkResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLinkResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateLinkResponse' :: CreateLinkResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateLinkResponse
s@CreateLinkResponse' {} Maybe (HashMap Text Text)
a -> CreateLinkResponse
s {$sel:tags:CreateLinkResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateLinkResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.NFData CreateLinkResponse where
  rnf :: CreateLinkResponse -> ()
rnf CreateLinkResponse' {Int
Maybe [Text]
Maybe Text
Maybe (HashMap Text Text)
httpStatus :: Int
tags :: Maybe (HashMap Text Text)
sinkArn :: Maybe Text
resourceTypes :: Maybe [Text]
labelTemplate :: Maybe Text
label :: Maybe Text
id :: Maybe Text
arn :: Maybe Text
$sel:httpStatus:CreateLinkResponse' :: CreateLinkResponse -> Int
$sel:tags:CreateLinkResponse' :: CreateLinkResponse -> Maybe (HashMap Text Text)
$sel:sinkArn:CreateLinkResponse' :: CreateLinkResponse -> Maybe Text
$sel:resourceTypes:CreateLinkResponse' :: CreateLinkResponse -> Maybe [Text]
$sel:labelTemplate:CreateLinkResponse' :: CreateLinkResponse -> Maybe Text
$sel:label:CreateLinkResponse' :: CreateLinkResponse -> Maybe Text
$sel:id:CreateLinkResponse' :: CreateLinkResponse -> Maybe Text
$sel:arn:CreateLinkResponse' :: CreateLinkResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
label
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
labelTemplate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
resourceTypes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sinkArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus