{-# 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.LakeFormation.AddLFTagsToResource
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Attaches one or more LF-tags to an existing resource.
module Amazonka.LakeFormation.AddLFTagsToResource
  ( -- * Creating a Request
    AddLFTagsToResource (..),
    newAddLFTagsToResource,

    -- * Request Lenses
    addLFTagsToResource_catalogId,
    addLFTagsToResource_resource,
    addLFTagsToResource_lFTags,

    -- * Destructuring the Response
    AddLFTagsToResourceResponse (..),
    newAddLFTagsToResourceResponse,

    -- * Response Lenses
    addLFTagsToResourceResponse_failures,
    addLFTagsToResourceResponse_httpStatus,
  )
where

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

-- | /See:/ 'newAddLFTagsToResource' smart constructor.
data AddLFTagsToResource = AddLFTagsToResource'
  { -- | The identifier for the Data Catalog. By default, the account ID. The
    -- Data Catalog is the persistent metadata store. It contains database
    -- definitions, table definitions, and other control information to manage
    -- your Lake Formation environment.
    AddLFTagsToResource -> Maybe Text
catalogId :: Prelude.Maybe Prelude.Text,
    -- | The database, table, or column resource to which to attach an LF-tag.
    AddLFTagsToResource -> Resource
resource :: Resource,
    -- | The LF-tags to attach to the resource.
    AddLFTagsToResource -> NonEmpty LFTagPair
lFTags :: Prelude.NonEmpty LFTagPair
  }
  deriving (AddLFTagsToResource -> AddLFTagsToResource -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddLFTagsToResource -> AddLFTagsToResource -> Bool
$c/= :: AddLFTagsToResource -> AddLFTagsToResource -> Bool
== :: AddLFTagsToResource -> AddLFTagsToResource -> Bool
$c== :: AddLFTagsToResource -> AddLFTagsToResource -> Bool
Prelude.Eq, ReadPrec [AddLFTagsToResource]
ReadPrec AddLFTagsToResource
Int -> ReadS AddLFTagsToResource
ReadS [AddLFTagsToResource]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AddLFTagsToResource]
$creadListPrec :: ReadPrec [AddLFTagsToResource]
readPrec :: ReadPrec AddLFTagsToResource
$creadPrec :: ReadPrec AddLFTagsToResource
readList :: ReadS [AddLFTagsToResource]
$creadList :: ReadS [AddLFTagsToResource]
readsPrec :: Int -> ReadS AddLFTagsToResource
$creadsPrec :: Int -> ReadS AddLFTagsToResource
Prelude.Read, Int -> AddLFTagsToResource -> ShowS
[AddLFTagsToResource] -> ShowS
AddLFTagsToResource -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddLFTagsToResource] -> ShowS
$cshowList :: [AddLFTagsToResource] -> ShowS
show :: AddLFTagsToResource -> String
$cshow :: AddLFTagsToResource -> String
showsPrec :: Int -> AddLFTagsToResource -> ShowS
$cshowsPrec :: Int -> AddLFTagsToResource -> ShowS
Prelude.Show, forall x. Rep AddLFTagsToResource x -> AddLFTagsToResource
forall x. AddLFTagsToResource -> Rep AddLFTagsToResource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddLFTagsToResource x -> AddLFTagsToResource
$cfrom :: forall x. AddLFTagsToResource -> Rep AddLFTagsToResource x
Prelude.Generic)

-- |
-- Create a value of 'AddLFTagsToResource' 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:
--
-- 'catalogId', 'addLFTagsToResource_catalogId' - The identifier for the Data Catalog. By default, the account ID. The
-- Data Catalog is the persistent metadata store. It contains database
-- definitions, table definitions, and other control information to manage
-- your Lake Formation environment.
--
-- 'resource', 'addLFTagsToResource_resource' - The database, table, or column resource to which to attach an LF-tag.
--
-- 'lFTags', 'addLFTagsToResource_lFTags' - The LF-tags to attach to the resource.
newAddLFTagsToResource ::
  -- | 'resource'
  Resource ->
  -- | 'lFTags'
  Prelude.NonEmpty LFTagPair ->
  AddLFTagsToResource
newAddLFTagsToResource :: Resource -> NonEmpty LFTagPair -> AddLFTagsToResource
newAddLFTagsToResource Resource
pResource_ NonEmpty LFTagPair
pLFTags_ =
  AddLFTagsToResource'
    { $sel:catalogId:AddLFTagsToResource' :: Maybe Text
catalogId = forall a. Maybe a
Prelude.Nothing,
      $sel:resource:AddLFTagsToResource' :: Resource
resource = Resource
pResource_,
      $sel:lFTags:AddLFTagsToResource' :: NonEmpty LFTagPair
lFTags = 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 LFTagPair
pLFTags_
    }

-- | The identifier for the Data Catalog. By default, the account ID. The
-- Data Catalog is the persistent metadata store. It contains database
-- definitions, table definitions, and other control information to manage
-- your Lake Formation environment.
addLFTagsToResource_catalogId :: Lens.Lens' AddLFTagsToResource (Prelude.Maybe Prelude.Text)
addLFTagsToResource_catalogId :: Lens' AddLFTagsToResource (Maybe Text)
addLFTagsToResource_catalogId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddLFTagsToResource' {Maybe Text
catalogId :: Maybe Text
$sel:catalogId:AddLFTagsToResource' :: AddLFTagsToResource -> Maybe Text
catalogId} -> Maybe Text
catalogId) (\s :: AddLFTagsToResource
s@AddLFTagsToResource' {} Maybe Text
a -> AddLFTagsToResource
s {$sel:catalogId:AddLFTagsToResource' :: Maybe Text
catalogId = Maybe Text
a} :: AddLFTagsToResource)

-- | The database, table, or column resource to which to attach an LF-tag.
addLFTagsToResource_resource :: Lens.Lens' AddLFTagsToResource Resource
addLFTagsToResource_resource :: Lens' AddLFTagsToResource Resource
addLFTagsToResource_resource = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddLFTagsToResource' {Resource
resource :: Resource
$sel:resource:AddLFTagsToResource' :: AddLFTagsToResource -> Resource
resource} -> Resource
resource) (\s :: AddLFTagsToResource
s@AddLFTagsToResource' {} Resource
a -> AddLFTagsToResource
s {$sel:resource:AddLFTagsToResource' :: Resource
resource = Resource
a} :: AddLFTagsToResource)

-- | The LF-tags to attach to the resource.
addLFTagsToResource_lFTags :: Lens.Lens' AddLFTagsToResource (Prelude.NonEmpty LFTagPair)
addLFTagsToResource_lFTags :: Lens' AddLFTagsToResource (NonEmpty LFTagPair)
addLFTagsToResource_lFTags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddLFTagsToResource' {NonEmpty LFTagPair
lFTags :: NonEmpty LFTagPair
$sel:lFTags:AddLFTagsToResource' :: AddLFTagsToResource -> NonEmpty LFTagPair
lFTags} -> NonEmpty LFTagPair
lFTags) (\s :: AddLFTagsToResource
s@AddLFTagsToResource' {} NonEmpty LFTagPair
a -> AddLFTagsToResource
s {$sel:lFTags:AddLFTagsToResource' :: NonEmpty LFTagPair
lFTags = NonEmpty LFTagPair
a} :: AddLFTagsToResource) 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 AddLFTagsToResource where
  type
    AWSResponse AddLFTagsToResource =
      AddLFTagsToResourceResponse
  request :: (Service -> Service)
-> AddLFTagsToResource -> Request AddLFTagsToResource
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 AddLFTagsToResource
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AddLFTagsToResource)))
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 [LFTagError] -> Int -> AddLFTagsToResourceResponse
AddLFTagsToResourceResponse'
            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
"Failures" 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 AddLFTagsToResource where
  hashWithSalt :: Int -> AddLFTagsToResource -> Int
hashWithSalt Int
_salt AddLFTagsToResource' {Maybe Text
NonEmpty LFTagPair
Resource
lFTags :: NonEmpty LFTagPair
resource :: Resource
catalogId :: Maybe Text
$sel:lFTags:AddLFTagsToResource' :: AddLFTagsToResource -> NonEmpty LFTagPair
$sel:resource:AddLFTagsToResource' :: AddLFTagsToResource -> Resource
$sel:catalogId:AddLFTagsToResource' :: AddLFTagsToResource -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
catalogId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Resource
resource
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty LFTagPair
lFTags

instance Prelude.NFData AddLFTagsToResource where
  rnf :: AddLFTagsToResource -> ()
rnf AddLFTagsToResource' {Maybe Text
NonEmpty LFTagPair
Resource
lFTags :: NonEmpty LFTagPair
resource :: Resource
catalogId :: Maybe Text
$sel:lFTags:AddLFTagsToResource' :: AddLFTagsToResource -> NonEmpty LFTagPair
$sel:resource:AddLFTagsToResource' :: AddLFTagsToResource -> Resource
$sel:catalogId:AddLFTagsToResource' :: AddLFTagsToResource -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
catalogId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Resource
resource
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty LFTagPair
lFTags

instance Data.ToHeaders AddLFTagsToResource where
  toHeaders :: AddLFTagsToResource -> 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 AddLFTagsToResource where
  toJSON :: AddLFTagsToResource -> Value
toJSON AddLFTagsToResource' {Maybe Text
NonEmpty LFTagPair
Resource
lFTags :: NonEmpty LFTagPair
resource :: Resource
catalogId :: Maybe Text
$sel:lFTags:AddLFTagsToResource' :: AddLFTagsToResource -> NonEmpty LFTagPair
$sel:resource:AddLFTagsToResource' :: AddLFTagsToResource -> Resource
$sel:catalogId:AddLFTagsToResource' :: AddLFTagsToResource -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"CatalogId" 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 Text
catalogId,
            forall a. a -> Maybe a
Prelude.Just (Key
"Resource" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Resource
resource),
            forall a. a -> Maybe a
Prelude.Just (Key
"LFTags" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty LFTagPair
lFTags)
          ]
      )

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

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

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

-- |
-- Create a value of 'AddLFTagsToResourceResponse' 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:
--
-- 'failures', 'addLFTagsToResourceResponse_failures' - A list of failures to tag the resource.
--
-- 'httpStatus', 'addLFTagsToResourceResponse_httpStatus' - The response's http status code.
newAddLFTagsToResourceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  AddLFTagsToResourceResponse
newAddLFTagsToResourceResponse :: Int -> AddLFTagsToResourceResponse
newAddLFTagsToResourceResponse Int
pHttpStatus_ =
  AddLFTagsToResourceResponse'
    { $sel:failures:AddLFTagsToResourceResponse' :: Maybe [LFTagError]
failures =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:AddLFTagsToResourceResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of failures to tag the resource.
addLFTagsToResourceResponse_failures :: Lens.Lens' AddLFTagsToResourceResponse (Prelude.Maybe [LFTagError])
addLFTagsToResourceResponse_failures :: Lens' AddLFTagsToResourceResponse (Maybe [LFTagError])
addLFTagsToResourceResponse_failures = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddLFTagsToResourceResponse' {Maybe [LFTagError]
failures :: Maybe [LFTagError]
$sel:failures:AddLFTagsToResourceResponse' :: AddLFTagsToResourceResponse -> Maybe [LFTagError]
failures} -> Maybe [LFTagError]
failures) (\s :: AddLFTagsToResourceResponse
s@AddLFTagsToResourceResponse' {} Maybe [LFTagError]
a -> AddLFTagsToResourceResponse
s {$sel:failures:AddLFTagsToResourceResponse' :: Maybe [LFTagError]
failures = Maybe [LFTagError]
a} :: AddLFTagsToResourceResponse) 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.
addLFTagsToResourceResponse_httpStatus :: Lens.Lens' AddLFTagsToResourceResponse Prelude.Int
addLFTagsToResourceResponse_httpStatus :: Lens' AddLFTagsToResourceResponse Int
addLFTagsToResourceResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddLFTagsToResourceResponse' {Int
httpStatus :: Int
$sel:httpStatus:AddLFTagsToResourceResponse' :: AddLFTagsToResourceResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: AddLFTagsToResourceResponse
s@AddLFTagsToResourceResponse' {} Int
a -> AddLFTagsToResourceResponse
s {$sel:httpStatus:AddLFTagsToResourceResponse' :: Int
httpStatus = Int
a} :: AddLFTagsToResourceResponse)

instance Prelude.NFData AddLFTagsToResourceResponse where
  rnf :: AddLFTagsToResourceResponse -> ()
rnf AddLFTagsToResourceResponse' {Int
Maybe [LFTagError]
httpStatus :: Int
failures :: Maybe [LFTagError]
$sel:httpStatus:AddLFTagsToResourceResponse' :: AddLFTagsToResourceResponse -> Int
$sel:failures:AddLFTagsToResourceResponse' :: AddLFTagsToResourceResponse -> Maybe [LFTagError]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [LFTagError]
failures
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus