{-# 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.Discovery.StopDataCollectionByAgentIds
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Instructs the specified agents or connectors to stop collecting data.
module Amazonka.Discovery.StopDataCollectionByAgentIds
  ( -- * Creating a Request
    StopDataCollectionByAgentIds (..),
    newStopDataCollectionByAgentIds,

    -- * Request Lenses
    stopDataCollectionByAgentIds_agentIds,

    -- * Destructuring the Response
    StopDataCollectionByAgentIdsResponse (..),
    newStopDataCollectionByAgentIdsResponse,

    -- * Response Lenses
    stopDataCollectionByAgentIdsResponse_agentsConfigurationStatus,
    stopDataCollectionByAgentIdsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newStopDataCollectionByAgentIds' smart constructor.
data StopDataCollectionByAgentIds = StopDataCollectionByAgentIds'
  { -- | The IDs of the agents or connectors from which to stop collecting data.
    StopDataCollectionByAgentIds -> [Text]
agentIds :: [Prelude.Text]
  }
  deriving (StopDataCollectionByAgentIds
-> StopDataCollectionByAgentIds -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopDataCollectionByAgentIds
-> StopDataCollectionByAgentIds -> Bool
$c/= :: StopDataCollectionByAgentIds
-> StopDataCollectionByAgentIds -> Bool
== :: StopDataCollectionByAgentIds
-> StopDataCollectionByAgentIds -> Bool
$c== :: StopDataCollectionByAgentIds
-> StopDataCollectionByAgentIds -> Bool
Prelude.Eq, ReadPrec [StopDataCollectionByAgentIds]
ReadPrec StopDataCollectionByAgentIds
Int -> ReadS StopDataCollectionByAgentIds
ReadS [StopDataCollectionByAgentIds]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopDataCollectionByAgentIds]
$creadListPrec :: ReadPrec [StopDataCollectionByAgentIds]
readPrec :: ReadPrec StopDataCollectionByAgentIds
$creadPrec :: ReadPrec StopDataCollectionByAgentIds
readList :: ReadS [StopDataCollectionByAgentIds]
$creadList :: ReadS [StopDataCollectionByAgentIds]
readsPrec :: Int -> ReadS StopDataCollectionByAgentIds
$creadsPrec :: Int -> ReadS StopDataCollectionByAgentIds
Prelude.Read, Int -> StopDataCollectionByAgentIds -> ShowS
[StopDataCollectionByAgentIds] -> ShowS
StopDataCollectionByAgentIds -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopDataCollectionByAgentIds] -> ShowS
$cshowList :: [StopDataCollectionByAgentIds] -> ShowS
show :: StopDataCollectionByAgentIds -> String
$cshow :: StopDataCollectionByAgentIds -> String
showsPrec :: Int -> StopDataCollectionByAgentIds -> ShowS
$cshowsPrec :: Int -> StopDataCollectionByAgentIds -> ShowS
Prelude.Show, forall x.
Rep StopDataCollectionByAgentIds x -> StopDataCollectionByAgentIds
forall x.
StopDataCollectionByAgentIds -> Rep StopDataCollectionByAgentIds x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StopDataCollectionByAgentIds x -> StopDataCollectionByAgentIds
$cfrom :: forall x.
StopDataCollectionByAgentIds -> Rep StopDataCollectionByAgentIds x
Prelude.Generic)

-- |
-- Create a value of 'StopDataCollectionByAgentIds' 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:
--
-- 'agentIds', 'stopDataCollectionByAgentIds_agentIds' - The IDs of the agents or connectors from which to stop collecting data.
newStopDataCollectionByAgentIds ::
  StopDataCollectionByAgentIds
newStopDataCollectionByAgentIds :: StopDataCollectionByAgentIds
newStopDataCollectionByAgentIds =
  StopDataCollectionByAgentIds'
    { $sel:agentIds:StopDataCollectionByAgentIds' :: [Text]
agentIds =
        forall a. Monoid a => a
Prelude.mempty
    }

-- | The IDs of the agents or connectors from which to stop collecting data.
stopDataCollectionByAgentIds_agentIds :: Lens.Lens' StopDataCollectionByAgentIds [Prelude.Text]
stopDataCollectionByAgentIds_agentIds :: Lens' StopDataCollectionByAgentIds [Text]
stopDataCollectionByAgentIds_agentIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopDataCollectionByAgentIds' {[Text]
agentIds :: [Text]
$sel:agentIds:StopDataCollectionByAgentIds' :: StopDataCollectionByAgentIds -> [Text]
agentIds} -> [Text]
agentIds) (\s :: StopDataCollectionByAgentIds
s@StopDataCollectionByAgentIds' {} [Text]
a -> StopDataCollectionByAgentIds
s {$sel:agentIds:StopDataCollectionByAgentIds' :: [Text]
agentIds = [Text]
a} :: StopDataCollectionByAgentIds) 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 StopDataCollectionByAgentIds where
  type
    AWSResponse StopDataCollectionByAgentIds =
      StopDataCollectionByAgentIdsResponse
  request :: (Service -> Service)
-> StopDataCollectionByAgentIds
-> Request StopDataCollectionByAgentIds
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 StopDataCollectionByAgentIds
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse StopDataCollectionByAgentIds)))
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 [AgentConfigurationStatus]
-> Int -> StopDataCollectionByAgentIdsResponse
StopDataCollectionByAgentIdsResponse'
            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
"agentsConfigurationStatus"
                            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
    StopDataCollectionByAgentIds
  where
  hashWithSalt :: Int -> StopDataCollectionByAgentIds -> Int
hashWithSalt Int
_salt StopDataCollectionByAgentIds' {[Text]
agentIds :: [Text]
$sel:agentIds:StopDataCollectionByAgentIds' :: StopDataCollectionByAgentIds -> [Text]
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
agentIds

instance Prelude.NFData StopDataCollectionByAgentIds where
  rnf :: StopDataCollectionByAgentIds -> ()
rnf StopDataCollectionByAgentIds' {[Text]
agentIds :: [Text]
$sel:agentIds:StopDataCollectionByAgentIds' :: StopDataCollectionByAgentIds -> [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf [Text]
agentIds

instance Data.ToHeaders StopDataCollectionByAgentIds where
  toHeaders :: StopDataCollectionByAgentIds -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AWSPoseidonService_V2015_11_01.StopDataCollectionByAgentIds" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

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

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

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

-- | /See:/ 'newStopDataCollectionByAgentIdsResponse' smart constructor.
data StopDataCollectionByAgentIdsResponse = StopDataCollectionByAgentIdsResponse'
  { -- | Information about the agents or connector that were instructed to stop
    -- collecting data. Information includes the agent\/connector ID, a
    -- description of the operation performed, and whether the agent\/connector
    -- configuration was updated.
    StopDataCollectionByAgentIdsResponse
-> Maybe [AgentConfigurationStatus]
agentsConfigurationStatus :: Prelude.Maybe [AgentConfigurationStatus],
    -- | The response's http status code.
    StopDataCollectionByAgentIdsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StopDataCollectionByAgentIdsResponse
-> StopDataCollectionByAgentIdsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopDataCollectionByAgentIdsResponse
-> StopDataCollectionByAgentIdsResponse -> Bool
$c/= :: StopDataCollectionByAgentIdsResponse
-> StopDataCollectionByAgentIdsResponse -> Bool
== :: StopDataCollectionByAgentIdsResponse
-> StopDataCollectionByAgentIdsResponse -> Bool
$c== :: StopDataCollectionByAgentIdsResponse
-> StopDataCollectionByAgentIdsResponse -> Bool
Prelude.Eq, ReadPrec [StopDataCollectionByAgentIdsResponse]
ReadPrec StopDataCollectionByAgentIdsResponse
Int -> ReadS StopDataCollectionByAgentIdsResponse
ReadS [StopDataCollectionByAgentIdsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopDataCollectionByAgentIdsResponse]
$creadListPrec :: ReadPrec [StopDataCollectionByAgentIdsResponse]
readPrec :: ReadPrec StopDataCollectionByAgentIdsResponse
$creadPrec :: ReadPrec StopDataCollectionByAgentIdsResponse
readList :: ReadS [StopDataCollectionByAgentIdsResponse]
$creadList :: ReadS [StopDataCollectionByAgentIdsResponse]
readsPrec :: Int -> ReadS StopDataCollectionByAgentIdsResponse
$creadsPrec :: Int -> ReadS StopDataCollectionByAgentIdsResponse
Prelude.Read, Int -> StopDataCollectionByAgentIdsResponse -> ShowS
[StopDataCollectionByAgentIdsResponse] -> ShowS
StopDataCollectionByAgentIdsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopDataCollectionByAgentIdsResponse] -> ShowS
$cshowList :: [StopDataCollectionByAgentIdsResponse] -> ShowS
show :: StopDataCollectionByAgentIdsResponse -> String
$cshow :: StopDataCollectionByAgentIdsResponse -> String
showsPrec :: Int -> StopDataCollectionByAgentIdsResponse -> ShowS
$cshowsPrec :: Int -> StopDataCollectionByAgentIdsResponse -> ShowS
Prelude.Show, forall x.
Rep StopDataCollectionByAgentIdsResponse x
-> StopDataCollectionByAgentIdsResponse
forall x.
StopDataCollectionByAgentIdsResponse
-> Rep StopDataCollectionByAgentIdsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StopDataCollectionByAgentIdsResponse x
-> StopDataCollectionByAgentIdsResponse
$cfrom :: forall x.
StopDataCollectionByAgentIdsResponse
-> Rep StopDataCollectionByAgentIdsResponse x
Prelude.Generic)

-- |
-- Create a value of 'StopDataCollectionByAgentIdsResponse' 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:
--
-- 'agentsConfigurationStatus', 'stopDataCollectionByAgentIdsResponse_agentsConfigurationStatus' - Information about the agents or connector that were instructed to stop
-- collecting data. Information includes the agent\/connector ID, a
-- description of the operation performed, and whether the agent\/connector
-- configuration was updated.
--
-- 'httpStatus', 'stopDataCollectionByAgentIdsResponse_httpStatus' - The response's http status code.
newStopDataCollectionByAgentIdsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StopDataCollectionByAgentIdsResponse
newStopDataCollectionByAgentIdsResponse :: Int -> StopDataCollectionByAgentIdsResponse
newStopDataCollectionByAgentIdsResponse Int
pHttpStatus_ =
  StopDataCollectionByAgentIdsResponse'
    { $sel:agentsConfigurationStatus:StopDataCollectionByAgentIdsResponse' :: Maybe [AgentConfigurationStatus]
agentsConfigurationStatus =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StopDataCollectionByAgentIdsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the agents or connector that were instructed to stop
-- collecting data. Information includes the agent\/connector ID, a
-- description of the operation performed, and whether the agent\/connector
-- configuration was updated.
stopDataCollectionByAgentIdsResponse_agentsConfigurationStatus :: Lens.Lens' StopDataCollectionByAgentIdsResponse (Prelude.Maybe [AgentConfigurationStatus])
stopDataCollectionByAgentIdsResponse_agentsConfigurationStatus :: Lens'
  StopDataCollectionByAgentIdsResponse
  (Maybe [AgentConfigurationStatus])
stopDataCollectionByAgentIdsResponse_agentsConfigurationStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopDataCollectionByAgentIdsResponse' {Maybe [AgentConfigurationStatus]
agentsConfigurationStatus :: Maybe [AgentConfigurationStatus]
$sel:agentsConfigurationStatus:StopDataCollectionByAgentIdsResponse' :: StopDataCollectionByAgentIdsResponse
-> Maybe [AgentConfigurationStatus]
agentsConfigurationStatus} -> Maybe [AgentConfigurationStatus]
agentsConfigurationStatus) (\s :: StopDataCollectionByAgentIdsResponse
s@StopDataCollectionByAgentIdsResponse' {} Maybe [AgentConfigurationStatus]
a -> StopDataCollectionByAgentIdsResponse
s {$sel:agentsConfigurationStatus:StopDataCollectionByAgentIdsResponse' :: Maybe [AgentConfigurationStatus]
agentsConfigurationStatus = Maybe [AgentConfigurationStatus]
a} :: StopDataCollectionByAgentIdsResponse) 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.
stopDataCollectionByAgentIdsResponse_httpStatus :: Lens.Lens' StopDataCollectionByAgentIdsResponse Prelude.Int
stopDataCollectionByAgentIdsResponse_httpStatus :: Lens' StopDataCollectionByAgentIdsResponse Int
stopDataCollectionByAgentIdsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopDataCollectionByAgentIdsResponse' {Int
httpStatus :: Int
$sel:httpStatus:StopDataCollectionByAgentIdsResponse' :: StopDataCollectionByAgentIdsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: StopDataCollectionByAgentIdsResponse
s@StopDataCollectionByAgentIdsResponse' {} Int
a -> StopDataCollectionByAgentIdsResponse
s {$sel:httpStatus:StopDataCollectionByAgentIdsResponse' :: Int
httpStatus = Int
a} :: StopDataCollectionByAgentIdsResponse)

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