{-# 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.ResourceGroups.GroupResources
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Adds the specified resources to the specified group.
--
-- __Minimum permissions__
--
-- To run this command, you must have the following permissions:
--
-- -   @resource-groups:GroupResources@
module Amazonka.ResourceGroups.GroupResources
  ( -- * Creating a Request
    GroupResources (..),
    newGroupResources,

    -- * Request Lenses
    groupResources_group,
    groupResources_resourceArns,

    -- * Destructuring the Response
    GroupResourcesResponse (..),
    newGroupResourcesResponse,

    -- * Response Lenses
    groupResourcesResponse_failed,
    groupResourcesResponse_pending,
    groupResourcesResponse_succeeded,
    groupResourcesResponse_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 Amazonka.ResourceGroups.Types
import qualified Amazonka.Response as Response

-- | /See:/ 'newGroupResources' smart constructor.
data GroupResources = GroupResources'
  { -- | The name or the ARN of the resource group to add resources to.
    GroupResources -> Text
group' :: Prelude.Text,
    -- | The list of ARNs for resources to be added to the group.
    GroupResources -> NonEmpty Text
resourceArns :: Prelude.NonEmpty Prelude.Text
  }
  deriving (GroupResources -> GroupResources -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GroupResources -> GroupResources -> Bool
$c/= :: GroupResources -> GroupResources -> Bool
== :: GroupResources -> GroupResources -> Bool
$c== :: GroupResources -> GroupResources -> Bool
Prelude.Eq, ReadPrec [GroupResources]
ReadPrec GroupResources
Int -> ReadS GroupResources
ReadS [GroupResources]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GroupResources]
$creadListPrec :: ReadPrec [GroupResources]
readPrec :: ReadPrec GroupResources
$creadPrec :: ReadPrec GroupResources
readList :: ReadS [GroupResources]
$creadList :: ReadS [GroupResources]
readsPrec :: Int -> ReadS GroupResources
$creadsPrec :: Int -> ReadS GroupResources
Prelude.Read, Int -> GroupResources -> ShowS
[GroupResources] -> ShowS
GroupResources -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GroupResources] -> ShowS
$cshowList :: [GroupResources] -> ShowS
show :: GroupResources -> String
$cshow :: GroupResources -> String
showsPrec :: Int -> GroupResources -> ShowS
$cshowsPrec :: Int -> GroupResources -> ShowS
Prelude.Show, forall x. Rep GroupResources x -> GroupResources
forall x. GroupResources -> Rep GroupResources x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GroupResources x -> GroupResources
$cfrom :: forall x. GroupResources -> Rep GroupResources x
Prelude.Generic)

-- |
-- Create a value of 'GroupResources' 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:
--
-- 'group'', 'groupResources_group' - The name or the ARN of the resource group to add resources to.
--
-- 'resourceArns', 'groupResources_resourceArns' - The list of ARNs for resources to be added to the group.
newGroupResources ::
  -- | 'group''
  Prelude.Text ->
  -- | 'resourceArns'
  Prelude.NonEmpty Prelude.Text ->
  GroupResources
newGroupResources :: Text -> NonEmpty Text -> GroupResources
newGroupResources Text
pGroup_ NonEmpty Text
pResourceArns_ =
  GroupResources'
    { $sel:group':GroupResources' :: Text
group' = Text
pGroup_,
      $sel:resourceArns:GroupResources' :: NonEmpty Text
resourceArns = 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 Text
pResourceArns_
    }

-- | The name or the ARN of the resource group to add resources to.
groupResources_group :: Lens.Lens' GroupResources Prelude.Text
groupResources_group :: Lens' GroupResources Text
groupResources_group = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GroupResources' {Text
group' :: Text
$sel:group':GroupResources' :: GroupResources -> Text
group'} -> Text
group') (\s :: GroupResources
s@GroupResources' {} Text
a -> GroupResources
s {$sel:group':GroupResources' :: Text
group' = Text
a} :: GroupResources)

-- | The list of ARNs for resources to be added to the group.
groupResources_resourceArns :: Lens.Lens' GroupResources (Prelude.NonEmpty Prelude.Text)
groupResources_resourceArns :: Lens' GroupResources (NonEmpty Text)
groupResources_resourceArns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GroupResources' {NonEmpty Text
resourceArns :: NonEmpty Text
$sel:resourceArns:GroupResources' :: GroupResources -> NonEmpty Text
resourceArns} -> NonEmpty Text
resourceArns) (\s :: GroupResources
s@GroupResources' {} NonEmpty Text
a -> GroupResources
s {$sel:resourceArns:GroupResources' :: NonEmpty Text
resourceArns = NonEmpty Text
a} :: GroupResources) 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 GroupResources where
  type
    AWSResponse GroupResources =
      GroupResourcesResponse
  request :: (Service -> Service) -> GroupResources -> Request GroupResources
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 GroupResources
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GroupResources)))
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 [FailedResource]
-> Maybe [PendingResource]
-> Maybe (NonEmpty Text)
-> Int
-> GroupResourcesResponse
GroupResourcesResponse'
            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
"Failed" 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
"Pending" 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
"Succeeded")
            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 GroupResources where
  hashWithSalt :: Int -> GroupResources -> Int
hashWithSalt Int
_salt GroupResources' {NonEmpty Text
Text
resourceArns :: NonEmpty Text
group' :: Text
$sel:resourceArns:GroupResources' :: GroupResources -> NonEmpty Text
$sel:group':GroupResources' :: GroupResources -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
group'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty Text
resourceArns

instance Prelude.NFData GroupResources where
  rnf :: GroupResources -> ()
rnf GroupResources' {NonEmpty Text
Text
resourceArns :: NonEmpty Text
group' :: Text
$sel:resourceArns:GroupResources' :: GroupResources -> NonEmpty Text
$sel:group':GroupResources' :: GroupResources -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
group'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty Text
resourceArns

instance Data.ToHeaders GroupResources where
  toHeaders :: GroupResources -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON GroupResources where
  toJSON :: GroupResources -> Value
toJSON GroupResources' {NonEmpty Text
Text
resourceArns :: NonEmpty Text
group' :: Text
$sel:resourceArns:GroupResources' :: GroupResources -> NonEmpty Text
$sel:group':GroupResources' :: GroupResources -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"Group" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
group'),
            forall a. a -> Maybe a
Prelude.Just (Key
"ResourceArns" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty Text
resourceArns)
          ]
      )

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

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

-- | /See:/ 'newGroupResourcesResponse' smart constructor.
data GroupResourcesResponse = GroupResourcesResponse'
  { -- | A list of ARNs of any resources that failed to be added to the group by
    -- this operation.
    GroupResourcesResponse -> Maybe [FailedResource]
failed :: Prelude.Maybe [FailedResource],
    -- | A list of ARNs of any resources that are still in the process of being
    -- added to the group by this operation. These pending additions continue
    -- asynchronously. You can check the status of pending additions by using
    -- the @ @@ListGroupResources@@ @ operation, and checking the @Resources@
    -- array in the response and the @Status@ field of each object in that
    -- array.
    GroupResourcesResponse -> Maybe [PendingResource]
pending :: Prelude.Maybe [PendingResource],
    -- | A list of ARNs of resources that were successfully added to the group by
    -- this operation.
    GroupResourcesResponse -> Maybe (NonEmpty Text)
succeeded :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | The response's http status code.
    GroupResourcesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GroupResourcesResponse -> GroupResourcesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GroupResourcesResponse -> GroupResourcesResponse -> Bool
$c/= :: GroupResourcesResponse -> GroupResourcesResponse -> Bool
== :: GroupResourcesResponse -> GroupResourcesResponse -> Bool
$c== :: GroupResourcesResponse -> GroupResourcesResponse -> Bool
Prelude.Eq, ReadPrec [GroupResourcesResponse]
ReadPrec GroupResourcesResponse
Int -> ReadS GroupResourcesResponse
ReadS [GroupResourcesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GroupResourcesResponse]
$creadListPrec :: ReadPrec [GroupResourcesResponse]
readPrec :: ReadPrec GroupResourcesResponse
$creadPrec :: ReadPrec GroupResourcesResponse
readList :: ReadS [GroupResourcesResponse]
$creadList :: ReadS [GroupResourcesResponse]
readsPrec :: Int -> ReadS GroupResourcesResponse
$creadsPrec :: Int -> ReadS GroupResourcesResponse
Prelude.Read, Int -> GroupResourcesResponse -> ShowS
[GroupResourcesResponse] -> ShowS
GroupResourcesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GroupResourcesResponse] -> ShowS
$cshowList :: [GroupResourcesResponse] -> ShowS
show :: GroupResourcesResponse -> String
$cshow :: GroupResourcesResponse -> String
showsPrec :: Int -> GroupResourcesResponse -> ShowS
$cshowsPrec :: Int -> GroupResourcesResponse -> ShowS
Prelude.Show, forall x. Rep GroupResourcesResponse x -> GroupResourcesResponse
forall x. GroupResourcesResponse -> Rep GroupResourcesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GroupResourcesResponse x -> GroupResourcesResponse
$cfrom :: forall x. GroupResourcesResponse -> Rep GroupResourcesResponse x
Prelude.Generic)

-- |
-- Create a value of 'GroupResourcesResponse' 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:
--
-- 'failed', 'groupResourcesResponse_failed' - A list of ARNs of any resources that failed to be added to the group by
-- this operation.
--
-- 'pending', 'groupResourcesResponse_pending' - A list of ARNs of any resources that are still in the process of being
-- added to the group by this operation. These pending additions continue
-- asynchronously. You can check the status of pending additions by using
-- the @ @@ListGroupResources@@ @ operation, and checking the @Resources@
-- array in the response and the @Status@ field of each object in that
-- array.
--
-- 'succeeded', 'groupResourcesResponse_succeeded' - A list of ARNs of resources that were successfully added to the group by
-- this operation.
--
-- 'httpStatus', 'groupResourcesResponse_httpStatus' - The response's http status code.
newGroupResourcesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GroupResourcesResponse
newGroupResourcesResponse :: Int -> GroupResourcesResponse
newGroupResourcesResponse Int
pHttpStatus_ =
  GroupResourcesResponse'
    { $sel:failed:GroupResourcesResponse' :: Maybe [FailedResource]
failed = forall a. Maybe a
Prelude.Nothing,
      $sel:pending:GroupResourcesResponse' :: Maybe [PendingResource]
pending = forall a. Maybe a
Prelude.Nothing,
      $sel:succeeded:GroupResourcesResponse' :: Maybe (NonEmpty Text)
succeeded = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GroupResourcesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of ARNs of any resources that failed to be added to the group by
-- this operation.
groupResourcesResponse_failed :: Lens.Lens' GroupResourcesResponse (Prelude.Maybe [FailedResource])
groupResourcesResponse_failed :: Lens' GroupResourcesResponse (Maybe [FailedResource])
groupResourcesResponse_failed = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GroupResourcesResponse' {Maybe [FailedResource]
failed :: Maybe [FailedResource]
$sel:failed:GroupResourcesResponse' :: GroupResourcesResponse -> Maybe [FailedResource]
failed} -> Maybe [FailedResource]
failed) (\s :: GroupResourcesResponse
s@GroupResourcesResponse' {} Maybe [FailedResource]
a -> GroupResourcesResponse
s {$sel:failed:GroupResourcesResponse' :: Maybe [FailedResource]
failed = Maybe [FailedResource]
a} :: GroupResourcesResponse) 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

-- | A list of ARNs of any resources that are still in the process of being
-- added to the group by this operation. These pending additions continue
-- asynchronously. You can check the status of pending additions by using
-- the @ @@ListGroupResources@@ @ operation, and checking the @Resources@
-- array in the response and the @Status@ field of each object in that
-- array.
groupResourcesResponse_pending :: Lens.Lens' GroupResourcesResponse (Prelude.Maybe [PendingResource])
groupResourcesResponse_pending :: Lens' GroupResourcesResponse (Maybe [PendingResource])
groupResourcesResponse_pending = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GroupResourcesResponse' {Maybe [PendingResource]
pending :: Maybe [PendingResource]
$sel:pending:GroupResourcesResponse' :: GroupResourcesResponse -> Maybe [PendingResource]
pending} -> Maybe [PendingResource]
pending) (\s :: GroupResourcesResponse
s@GroupResourcesResponse' {} Maybe [PendingResource]
a -> GroupResourcesResponse
s {$sel:pending:GroupResourcesResponse' :: Maybe [PendingResource]
pending = Maybe [PendingResource]
a} :: GroupResourcesResponse) 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

-- | A list of ARNs of resources that were successfully added to the group by
-- this operation.
groupResourcesResponse_succeeded :: Lens.Lens' GroupResourcesResponse (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
groupResourcesResponse_succeeded :: Lens' GroupResourcesResponse (Maybe (NonEmpty Text))
groupResourcesResponse_succeeded = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GroupResourcesResponse' {Maybe (NonEmpty Text)
succeeded :: Maybe (NonEmpty Text)
$sel:succeeded:GroupResourcesResponse' :: GroupResourcesResponse -> Maybe (NonEmpty Text)
succeeded} -> Maybe (NonEmpty Text)
succeeded) (\s :: GroupResourcesResponse
s@GroupResourcesResponse' {} Maybe (NonEmpty Text)
a -> GroupResourcesResponse
s {$sel:succeeded:GroupResourcesResponse' :: Maybe (NonEmpty Text)
succeeded = Maybe (NonEmpty Text)
a} :: GroupResourcesResponse) 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.
groupResourcesResponse_httpStatus :: Lens.Lens' GroupResourcesResponse Prelude.Int
groupResourcesResponse_httpStatus :: Lens' GroupResourcesResponse Int
groupResourcesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GroupResourcesResponse' {Int
httpStatus :: Int
$sel:httpStatus:GroupResourcesResponse' :: GroupResourcesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GroupResourcesResponse
s@GroupResourcesResponse' {} Int
a -> GroupResourcesResponse
s {$sel:httpStatus:GroupResourcesResponse' :: Int
httpStatus = Int
a} :: GroupResourcesResponse)

instance Prelude.NFData GroupResourcesResponse where
  rnf :: GroupResourcesResponse -> ()
rnf GroupResourcesResponse' {Int
Maybe [FailedResource]
Maybe [PendingResource]
Maybe (NonEmpty Text)
httpStatus :: Int
succeeded :: Maybe (NonEmpty Text)
pending :: Maybe [PendingResource]
failed :: Maybe [FailedResource]
$sel:httpStatus:GroupResourcesResponse' :: GroupResourcesResponse -> Int
$sel:succeeded:GroupResourcesResponse' :: GroupResourcesResponse -> Maybe (NonEmpty Text)
$sel:pending:GroupResourcesResponse' :: GroupResourcesResponse -> Maybe [PendingResource]
$sel:failed:GroupResourcesResponse' :: GroupResourcesResponse -> Maybe [FailedResource]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [FailedResource]
failed
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [PendingResource]
pending
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Text)
succeeded
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus