{-# 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.XRay.UpdateGroup
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates a group resource.
module Amazonka.XRay.UpdateGroup
  ( -- * Creating a Request
    UpdateGroup (..),
    newUpdateGroup,

    -- * Request Lenses
    updateGroup_filterExpression,
    updateGroup_groupARN,
    updateGroup_groupName,
    updateGroup_insightsConfiguration,

    -- * Destructuring the Response
    UpdateGroupResponse (..),
    newUpdateGroupResponse,

    -- * Response Lenses
    updateGroupResponse_group,
    updateGroupResponse_httpStatus,
  )
where

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

-- | /See:/ 'newUpdateGroup' smart constructor.
data UpdateGroup = UpdateGroup'
  { -- | The updated filter expression defining criteria by which to group
    -- traces.
    UpdateGroup -> Maybe Text
filterExpression :: Prelude.Maybe Prelude.Text,
    -- | The ARN that was generated upon creation.
    UpdateGroup -> Maybe Text
groupARN :: Prelude.Maybe Prelude.Text,
    -- | The case-sensitive name of the group.
    UpdateGroup -> Maybe Text
groupName :: Prelude.Maybe Prelude.Text,
    -- | The structure containing configurations related to insights.
    --
    -- -   The InsightsEnabled boolean can be set to true to enable insights
    --     for the group or false to disable insights for the group.
    --
    -- -   The NotificationsEnabled boolean can be set to true to enable
    --     insights notifications for the group. Notifications can only be
    --     enabled on a group with InsightsEnabled set to true.
    UpdateGroup -> Maybe InsightsConfiguration
insightsConfiguration :: Prelude.Maybe InsightsConfiguration
  }
  deriving (UpdateGroup -> UpdateGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateGroup -> UpdateGroup -> Bool
$c/= :: UpdateGroup -> UpdateGroup -> Bool
== :: UpdateGroup -> UpdateGroup -> Bool
$c== :: UpdateGroup -> UpdateGroup -> Bool
Prelude.Eq, ReadPrec [UpdateGroup]
ReadPrec UpdateGroup
Int -> ReadS UpdateGroup
ReadS [UpdateGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateGroup]
$creadListPrec :: ReadPrec [UpdateGroup]
readPrec :: ReadPrec UpdateGroup
$creadPrec :: ReadPrec UpdateGroup
readList :: ReadS [UpdateGroup]
$creadList :: ReadS [UpdateGroup]
readsPrec :: Int -> ReadS UpdateGroup
$creadsPrec :: Int -> ReadS UpdateGroup
Prelude.Read, Int -> UpdateGroup -> ShowS
[UpdateGroup] -> ShowS
UpdateGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateGroup] -> ShowS
$cshowList :: [UpdateGroup] -> ShowS
show :: UpdateGroup -> String
$cshow :: UpdateGroup -> String
showsPrec :: Int -> UpdateGroup -> ShowS
$cshowsPrec :: Int -> UpdateGroup -> ShowS
Prelude.Show, forall x. Rep UpdateGroup x -> UpdateGroup
forall x. UpdateGroup -> Rep UpdateGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateGroup x -> UpdateGroup
$cfrom :: forall x. UpdateGroup -> Rep UpdateGroup x
Prelude.Generic)

-- |
-- Create a value of 'UpdateGroup' 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:
--
-- 'filterExpression', 'updateGroup_filterExpression' - The updated filter expression defining criteria by which to group
-- traces.
--
-- 'groupARN', 'updateGroup_groupARN' - The ARN that was generated upon creation.
--
-- 'groupName', 'updateGroup_groupName' - The case-sensitive name of the group.
--
-- 'insightsConfiguration', 'updateGroup_insightsConfiguration' - The structure containing configurations related to insights.
--
-- -   The InsightsEnabled boolean can be set to true to enable insights
--     for the group or false to disable insights for the group.
--
-- -   The NotificationsEnabled boolean can be set to true to enable
--     insights notifications for the group. Notifications can only be
--     enabled on a group with InsightsEnabled set to true.
newUpdateGroup ::
  UpdateGroup
newUpdateGroup :: UpdateGroup
newUpdateGroup =
  UpdateGroup'
    { $sel:filterExpression:UpdateGroup' :: Maybe Text
filterExpression = forall a. Maybe a
Prelude.Nothing,
      $sel:groupARN:UpdateGroup' :: Maybe Text
groupARN = forall a. Maybe a
Prelude.Nothing,
      $sel:groupName:UpdateGroup' :: Maybe Text
groupName = forall a. Maybe a
Prelude.Nothing,
      $sel:insightsConfiguration:UpdateGroup' :: Maybe InsightsConfiguration
insightsConfiguration = forall a. Maybe a
Prelude.Nothing
    }

-- | The updated filter expression defining criteria by which to group
-- traces.
updateGroup_filterExpression :: Lens.Lens' UpdateGroup (Prelude.Maybe Prelude.Text)
updateGroup_filterExpression :: Lens' UpdateGroup (Maybe Text)
updateGroup_filterExpression = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGroup' {Maybe Text
filterExpression :: Maybe Text
$sel:filterExpression:UpdateGroup' :: UpdateGroup -> Maybe Text
filterExpression} -> Maybe Text
filterExpression) (\s :: UpdateGroup
s@UpdateGroup' {} Maybe Text
a -> UpdateGroup
s {$sel:filterExpression:UpdateGroup' :: Maybe Text
filterExpression = Maybe Text
a} :: UpdateGroup)

-- | The ARN that was generated upon creation.
updateGroup_groupARN :: Lens.Lens' UpdateGroup (Prelude.Maybe Prelude.Text)
updateGroup_groupARN :: Lens' UpdateGroup (Maybe Text)
updateGroup_groupARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGroup' {Maybe Text
groupARN :: Maybe Text
$sel:groupARN:UpdateGroup' :: UpdateGroup -> Maybe Text
groupARN} -> Maybe Text
groupARN) (\s :: UpdateGroup
s@UpdateGroup' {} Maybe Text
a -> UpdateGroup
s {$sel:groupARN:UpdateGroup' :: Maybe Text
groupARN = Maybe Text
a} :: UpdateGroup)

-- | The case-sensitive name of the group.
updateGroup_groupName :: Lens.Lens' UpdateGroup (Prelude.Maybe Prelude.Text)
updateGroup_groupName :: Lens' UpdateGroup (Maybe Text)
updateGroup_groupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGroup' {Maybe Text
groupName :: Maybe Text
$sel:groupName:UpdateGroup' :: UpdateGroup -> Maybe Text
groupName} -> Maybe Text
groupName) (\s :: UpdateGroup
s@UpdateGroup' {} Maybe Text
a -> UpdateGroup
s {$sel:groupName:UpdateGroup' :: Maybe Text
groupName = Maybe Text
a} :: UpdateGroup)

-- | The structure containing configurations related to insights.
--
-- -   The InsightsEnabled boolean can be set to true to enable insights
--     for the group or false to disable insights for the group.
--
-- -   The NotificationsEnabled boolean can be set to true to enable
--     insights notifications for the group. Notifications can only be
--     enabled on a group with InsightsEnabled set to true.
updateGroup_insightsConfiguration :: Lens.Lens' UpdateGroup (Prelude.Maybe InsightsConfiguration)
updateGroup_insightsConfiguration :: Lens' UpdateGroup (Maybe InsightsConfiguration)
updateGroup_insightsConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGroup' {Maybe InsightsConfiguration
insightsConfiguration :: Maybe InsightsConfiguration
$sel:insightsConfiguration:UpdateGroup' :: UpdateGroup -> Maybe InsightsConfiguration
insightsConfiguration} -> Maybe InsightsConfiguration
insightsConfiguration) (\s :: UpdateGroup
s@UpdateGroup' {} Maybe InsightsConfiguration
a -> UpdateGroup
s {$sel:insightsConfiguration:UpdateGroup' :: Maybe InsightsConfiguration
insightsConfiguration = Maybe InsightsConfiguration
a} :: UpdateGroup)

instance Core.AWSRequest UpdateGroup where
  type AWSResponse UpdateGroup = UpdateGroupResponse
  request :: (Service -> Service) -> UpdateGroup -> Request UpdateGroup
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 UpdateGroup
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateGroup)))
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 Group -> Int -> UpdateGroupResponse
UpdateGroupResponse'
            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
"Group")
            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 UpdateGroup where
  hashWithSalt :: Int -> UpdateGroup -> Int
hashWithSalt Int
_salt UpdateGroup' {Maybe Text
Maybe InsightsConfiguration
insightsConfiguration :: Maybe InsightsConfiguration
groupName :: Maybe Text
groupARN :: Maybe Text
filterExpression :: Maybe Text
$sel:insightsConfiguration:UpdateGroup' :: UpdateGroup -> Maybe InsightsConfiguration
$sel:groupName:UpdateGroup' :: UpdateGroup -> Maybe Text
$sel:groupARN:UpdateGroup' :: UpdateGroup -> Maybe Text
$sel:filterExpression:UpdateGroup' :: UpdateGroup -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
filterExpression
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
groupARN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
groupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe InsightsConfiguration
insightsConfiguration

instance Prelude.NFData UpdateGroup where
  rnf :: UpdateGroup -> ()
rnf UpdateGroup' {Maybe Text
Maybe InsightsConfiguration
insightsConfiguration :: Maybe InsightsConfiguration
groupName :: Maybe Text
groupARN :: Maybe Text
filterExpression :: Maybe Text
$sel:insightsConfiguration:UpdateGroup' :: UpdateGroup -> Maybe InsightsConfiguration
$sel:groupName:UpdateGroup' :: UpdateGroup -> Maybe Text
$sel:groupARN:UpdateGroup' :: UpdateGroup -> Maybe Text
$sel:filterExpression:UpdateGroup' :: UpdateGroup -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
filterExpression
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
groupARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
groupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InsightsConfiguration
insightsConfiguration

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

instance Data.ToJSON UpdateGroup where
  toJSON :: UpdateGroup -> Value
toJSON UpdateGroup' {Maybe Text
Maybe InsightsConfiguration
insightsConfiguration :: Maybe InsightsConfiguration
groupName :: Maybe Text
groupARN :: Maybe Text
filterExpression :: Maybe Text
$sel:insightsConfiguration:UpdateGroup' :: UpdateGroup -> Maybe InsightsConfiguration
$sel:groupName:UpdateGroup' :: UpdateGroup -> Maybe Text
$sel:groupARN:UpdateGroup' :: UpdateGroup -> Maybe Text
$sel:filterExpression:UpdateGroup' :: UpdateGroup -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"FilterExpression" 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
filterExpression,
            (Key
"GroupARN" 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
groupARN,
            (Key
"GroupName" 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
groupName,
            (Key
"InsightsConfiguration" 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 InsightsConfiguration
insightsConfiguration
          ]
      )

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

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

-- | /See:/ 'newUpdateGroupResponse' smart constructor.
data UpdateGroupResponse = UpdateGroupResponse'
  { -- | The group that was updated. Contains the name of the group that was
    -- updated, the ARN of the group that was updated, the updated filter
    -- expression, and the updated insight configuration assigned to the group.
    UpdateGroupResponse -> Maybe Group
group' :: Prelude.Maybe Group,
    -- | The response's http status code.
    UpdateGroupResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateGroupResponse -> UpdateGroupResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateGroupResponse -> UpdateGroupResponse -> Bool
$c/= :: UpdateGroupResponse -> UpdateGroupResponse -> Bool
== :: UpdateGroupResponse -> UpdateGroupResponse -> Bool
$c== :: UpdateGroupResponse -> UpdateGroupResponse -> Bool
Prelude.Eq, ReadPrec [UpdateGroupResponse]
ReadPrec UpdateGroupResponse
Int -> ReadS UpdateGroupResponse
ReadS [UpdateGroupResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateGroupResponse]
$creadListPrec :: ReadPrec [UpdateGroupResponse]
readPrec :: ReadPrec UpdateGroupResponse
$creadPrec :: ReadPrec UpdateGroupResponse
readList :: ReadS [UpdateGroupResponse]
$creadList :: ReadS [UpdateGroupResponse]
readsPrec :: Int -> ReadS UpdateGroupResponse
$creadsPrec :: Int -> ReadS UpdateGroupResponse
Prelude.Read, Int -> UpdateGroupResponse -> ShowS
[UpdateGroupResponse] -> ShowS
UpdateGroupResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateGroupResponse] -> ShowS
$cshowList :: [UpdateGroupResponse] -> ShowS
show :: UpdateGroupResponse -> String
$cshow :: UpdateGroupResponse -> String
showsPrec :: Int -> UpdateGroupResponse -> ShowS
$cshowsPrec :: Int -> UpdateGroupResponse -> ShowS
Prelude.Show, forall x. Rep UpdateGroupResponse x -> UpdateGroupResponse
forall x. UpdateGroupResponse -> Rep UpdateGroupResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateGroupResponse x -> UpdateGroupResponse
$cfrom :: forall x. UpdateGroupResponse -> Rep UpdateGroupResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateGroupResponse' 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'', 'updateGroupResponse_group' - The group that was updated. Contains the name of the group that was
-- updated, the ARN of the group that was updated, the updated filter
-- expression, and the updated insight configuration assigned to the group.
--
-- 'httpStatus', 'updateGroupResponse_httpStatus' - The response's http status code.
newUpdateGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateGroupResponse
newUpdateGroupResponse :: Int -> UpdateGroupResponse
newUpdateGroupResponse Int
pHttpStatus_ =
  UpdateGroupResponse'
    { $sel:group':UpdateGroupResponse' :: Maybe Group
group' = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The group that was updated. Contains the name of the group that was
-- updated, the ARN of the group that was updated, the updated filter
-- expression, and the updated insight configuration assigned to the group.
updateGroupResponse_group :: Lens.Lens' UpdateGroupResponse (Prelude.Maybe Group)
updateGroupResponse_group :: Lens' UpdateGroupResponse (Maybe Group)
updateGroupResponse_group = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGroupResponse' {Maybe Group
group' :: Maybe Group
$sel:group':UpdateGroupResponse' :: UpdateGroupResponse -> Maybe Group
group'} -> Maybe Group
group') (\s :: UpdateGroupResponse
s@UpdateGroupResponse' {} Maybe Group
a -> UpdateGroupResponse
s {$sel:group':UpdateGroupResponse' :: Maybe Group
group' = Maybe Group
a} :: UpdateGroupResponse)

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

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