{-# 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.UpdateLink
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Use this operation to change what types of data are shared from a source
-- account to its linked monitoring account sink. You can\'t change the
-- sink or change the monitoring account with this operation.
--
-- To update the list of tags associated with the sink, use
-- <https://docs.aws.amazon.com/OAM/latest/APIReference/API_TagResource.html TagResource>.
module Amazonka.OAM.UpdateLink
  ( -- * Creating a Request
    UpdateLink (..),
    newUpdateLink,

    -- * Request Lenses
    updateLink_identifier,
    updateLink_resourceTypes,

    -- * Destructuring the Response
    UpdateLinkResponse (..),
    newUpdateLinkResponse,

    -- * Response Lenses
    updateLinkResponse_arn,
    updateLinkResponse_id,
    updateLinkResponse_label,
    updateLinkResponse_labelTemplate,
    updateLinkResponse_resourceTypes,
    updateLinkResponse_sinkArn,
    updateLinkResponse_tags,
    updateLinkResponse_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:/ 'newUpdateLink' smart constructor.
data UpdateLink = UpdateLink'
  { -- | The ARN of the link that you want to update.
    UpdateLink -> Text
identifier :: Prelude.Text,
    -- | An array of strings that define which types of data that the source
    -- account will send to the monitoring account.
    --
    -- Your input here replaces the current set of data types that are shared.
    UpdateLink -> NonEmpty ResourceType
resourceTypes :: Prelude.NonEmpty ResourceType
  }
  deriving (UpdateLink -> UpdateLink -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateLink -> UpdateLink -> Bool
$c/= :: UpdateLink -> UpdateLink -> Bool
== :: UpdateLink -> UpdateLink -> Bool
$c== :: UpdateLink -> UpdateLink -> Bool
Prelude.Eq, ReadPrec [UpdateLink]
ReadPrec UpdateLink
Int -> ReadS UpdateLink
ReadS [UpdateLink]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateLink]
$creadListPrec :: ReadPrec [UpdateLink]
readPrec :: ReadPrec UpdateLink
$creadPrec :: ReadPrec UpdateLink
readList :: ReadS [UpdateLink]
$creadList :: ReadS [UpdateLink]
readsPrec :: Int -> ReadS UpdateLink
$creadsPrec :: Int -> ReadS UpdateLink
Prelude.Read, Int -> UpdateLink -> ShowS
[UpdateLink] -> ShowS
UpdateLink -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateLink] -> ShowS
$cshowList :: [UpdateLink] -> ShowS
show :: UpdateLink -> String
$cshow :: UpdateLink -> String
showsPrec :: Int -> UpdateLink -> ShowS
$cshowsPrec :: Int -> UpdateLink -> ShowS
Prelude.Show, forall x. Rep UpdateLink x -> UpdateLink
forall x. UpdateLink -> Rep UpdateLink x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateLink x -> UpdateLink
$cfrom :: forall x. UpdateLink -> Rep UpdateLink x
Prelude.Generic)

-- |
-- Create a value of 'UpdateLink' 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:
--
-- 'identifier', 'updateLink_identifier' - The ARN of the link that you want to update.
--
-- 'resourceTypes', 'updateLink_resourceTypes' - An array of strings that define which types of data that the source
-- account will send to the monitoring account.
--
-- Your input here replaces the current set of data types that are shared.
newUpdateLink ::
  -- | 'identifier'
  Prelude.Text ->
  -- | 'resourceTypes'
  Prelude.NonEmpty ResourceType ->
  UpdateLink
newUpdateLink :: Text -> NonEmpty ResourceType -> UpdateLink
newUpdateLink Text
pIdentifier_ NonEmpty ResourceType
pResourceTypes_ =
  UpdateLink'
    { $sel:identifier:UpdateLink' :: Text
identifier = Text
pIdentifier_,
      $sel:resourceTypes:UpdateLink' :: 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_
    }

-- | The ARN of the link that you want to update.
updateLink_identifier :: Lens.Lens' UpdateLink Prelude.Text
updateLink_identifier :: Lens' UpdateLink Text
updateLink_identifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateLink' {Text
identifier :: Text
$sel:identifier:UpdateLink' :: UpdateLink -> Text
identifier} -> Text
identifier) (\s :: UpdateLink
s@UpdateLink' {} Text
a -> UpdateLink
s {$sel:identifier:UpdateLink' :: Text
identifier = Text
a} :: UpdateLink)

-- | An array of strings that define which types of data that the source
-- account will send to the monitoring account.
--
-- Your input here replaces the current set of data types that are shared.
updateLink_resourceTypes :: Lens.Lens' UpdateLink (Prelude.NonEmpty ResourceType)
updateLink_resourceTypes :: Lens' UpdateLink (NonEmpty ResourceType)
updateLink_resourceTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateLink' {NonEmpty ResourceType
resourceTypes :: NonEmpty ResourceType
$sel:resourceTypes:UpdateLink' :: UpdateLink -> NonEmpty ResourceType
resourceTypes} -> NonEmpty ResourceType
resourceTypes) (\s :: UpdateLink
s@UpdateLink' {} NonEmpty ResourceType
a -> UpdateLink
s {$sel:resourceTypes:UpdateLink' :: NonEmpty ResourceType
resourceTypes = NonEmpty ResourceType
a} :: UpdateLink) 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

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

instance Prelude.NFData UpdateLink where
  rnf :: UpdateLink -> ()
rnf UpdateLink' {NonEmpty ResourceType
Text
resourceTypes :: NonEmpty ResourceType
identifier :: Text
$sel:resourceTypes:UpdateLink' :: UpdateLink -> NonEmpty ResourceType
$sel:identifier:UpdateLink' :: UpdateLink -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
identifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty ResourceType
resourceTypes

instance Data.ToHeaders UpdateLink where
  toHeaders :: UpdateLink -> 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 UpdateLink where
  toJSON :: UpdateLink -> Value
toJSON UpdateLink' {NonEmpty ResourceType
Text
resourceTypes :: NonEmpty ResourceType
identifier :: Text
$sel:resourceTypes:UpdateLink' :: UpdateLink -> NonEmpty ResourceType
$sel:identifier:UpdateLink' :: UpdateLink -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"Identifier" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
identifier),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"ResourceTypes" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty ResourceType
resourceTypes)
          ]
      )

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

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

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

-- |
-- Create a value of 'UpdateLinkResponse' 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', 'updateLinkResponse_arn' - The ARN of the link that you have updated.
--
-- 'id', 'updateLinkResponse_id' - The random ID string that Amazon Web Services generated as part of the
-- sink ARN.
--
-- 'label', 'updateLinkResponse_label' - The label assigned to this link, with the variables resolved to their
-- actual values.
--
-- 'labelTemplate', 'updateLinkResponse_labelTemplate' - The exact label template that was specified when the link was created,
-- with the template variables not resolved.
--
-- 'resourceTypes', 'updateLinkResponse_resourceTypes' - The resource types now supported by this link.
--
-- 'sinkArn', 'updateLinkResponse_sinkArn' - The ARN of the sink that is used for this link.
--
-- 'tags', 'updateLinkResponse_tags' - The tags assigned to the link.
--
-- 'httpStatus', 'updateLinkResponse_httpStatus' - The response's http status code.
newUpdateLinkResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateLinkResponse
newUpdateLinkResponse :: Int -> UpdateLinkResponse
newUpdateLinkResponse Int
pHttpStatus_ =
  UpdateLinkResponse'
    { $sel:arn:UpdateLinkResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:id:UpdateLinkResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:label:UpdateLinkResponse' :: Maybe Text
label = forall a. Maybe a
Prelude.Nothing,
      $sel:labelTemplate:UpdateLinkResponse' :: Maybe Text
labelTemplate = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceTypes:UpdateLinkResponse' :: Maybe [Text]
resourceTypes = forall a. Maybe a
Prelude.Nothing,
      $sel:sinkArn:UpdateLinkResponse' :: Maybe Text
sinkArn = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:UpdateLinkResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateLinkResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ARN of the link that you have updated.
updateLinkResponse_arn :: Lens.Lens' UpdateLinkResponse (Prelude.Maybe Prelude.Text)
updateLinkResponse_arn :: Lens' UpdateLinkResponse (Maybe Text)
updateLinkResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateLinkResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:UpdateLinkResponse' :: UpdateLinkResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: UpdateLinkResponse
s@UpdateLinkResponse' {} Maybe Text
a -> UpdateLinkResponse
s {$sel:arn:UpdateLinkResponse' :: Maybe Text
arn = Maybe Text
a} :: UpdateLinkResponse)

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

-- | The label assigned to this link, with the variables resolved to their
-- actual values.
updateLinkResponse_label :: Lens.Lens' UpdateLinkResponse (Prelude.Maybe Prelude.Text)
updateLinkResponse_label :: Lens' UpdateLinkResponse (Maybe Text)
updateLinkResponse_label = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateLinkResponse' {Maybe Text
label :: Maybe Text
$sel:label:UpdateLinkResponse' :: UpdateLinkResponse -> Maybe Text
label} -> Maybe Text
label) (\s :: UpdateLinkResponse
s@UpdateLinkResponse' {} Maybe Text
a -> UpdateLinkResponse
s {$sel:label:UpdateLinkResponse' :: Maybe Text
label = Maybe Text
a} :: UpdateLinkResponse)

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

-- | The resource types now supported by this link.
updateLinkResponse_resourceTypes :: Lens.Lens' UpdateLinkResponse (Prelude.Maybe [Prelude.Text])
updateLinkResponse_resourceTypes :: Lens' UpdateLinkResponse (Maybe [Text])
updateLinkResponse_resourceTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateLinkResponse' {Maybe [Text]
resourceTypes :: Maybe [Text]
$sel:resourceTypes:UpdateLinkResponse' :: UpdateLinkResponse -> Maybe [Text]
resourceTypes} -> Maybe [Text]
resourceTypes) (\s :: UpdateLinkResponse
s@UpdateLinkResponse' {} Maybe [Text]
a -> UpdateLinkResponse
s {$sel:resourceTypes:UpdateLinkResponse' :: Maybe [Text]
resourceTypes = Maybe [Text]
a} :: UpdateLinkResponse) 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.
updateLinkResponse_sinkArn :: Lens.Lens' UpdateLinkResponse (Prelude.Maybe Prelude.Text)
updateLinkResponse_sinkArn :: Lens' UpdateLinkResponse (Maybe Text)
updateLinkResponse_sinkArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateLinkResponse' {Maybe Text
sinkArn :: Maybe Text
$sel:sinkArn:UpdateLinkResponse' :: UpdateLinkResponse -> Maybe Text
sinkArn} -> Maybe Text
sinkArn) (\s :: UpdateLinkResponse
s@UpdateLinkResponse' {} Maybe Text
a -> UpdateLinkResponse
s {$sel:sinkArn:UpdateLinkResponse' :: Maybe Text
sinkArn = Maybe Text
a} :: UpdateLinkResponse)

-- | The tags assigned to the link.
updateLinkResponse_tags :: Lens.Lens' UpdateLinkResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
updateLinkResponse_tags :: Lens' UpdateLinkResponse (Maybe (HashMap Text Text))
updateLinkResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateLinkResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:UpdateLinkResponse' :: UpdateLinkResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: UpdateLinkResponse
s@UpdateLinkResponse' {} Maybe (HashMap Text Text)
a -> UpdateLinkResponse
s {$sel:tags:UpdateLinkResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: UpdateLinkResponse) 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.
updateLinkResponse_httpStatus :: Lens.Lens' UpdateLinkResponse Prelude.Int
updateLinkResponse_httpStatus :: Lens' UpdateLinkResponse Int
updateLinkResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateLinkResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateLinkResponse' :: UpdateLinkResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdateLinkResponse
s@UpdateLinkResponse' {} Int
a -> UpdateLinkResponse
s {$sel:httpStatus:UpdateLinkResponse' :: Int
httpStatus = Int
a} :: UpdateLinkResponse)

instance Prelude.NFData UpdateLinkResponse where
  rnf :: UpdateLinkResponse -> ()
rnf UpdateLinkResponse' {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:UpdateLinkResponse' :: UpdateLinkResponse -> Int
$sel:tags:UpdateLinkResponse' :: UpdateLinkResponse -> Maybe (HashMap Text Text)
$sel:sinkArn:UpdateLinkResponse' :: UpdateLinkResponse -> Maybe Text
$sel:resourceTypes:UpdateLinkResponse' :: UpdateLinkResponse -> Maybe [Text]
$sel:labelTemplate:UpdateLinkResponse' :: UpdateLinkResponse -> Maybe Text
$sel:label:UpdateLinkResponse' :: UpdateLinkResponse -> Maybe Text
$sel:id:UpdateLinkResponse' :: UpdateLinkResponse -> Maybe Text
$sel:arn:UpdateLinkResponse' :: UpdateLinkResponse -> 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