{-# 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.Greengrass.ResetDeployments
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Resets a group\'s deployments.
module Amazonka.Greengrass.ResetDeployments
  ( -- * Creating a Request
    ResetDeployments (..),
    newResetDeployments,

    -- * Request Lenses
    resetDeployments_amznClientToken,
    resetDeployments_force,
    resetDeployments_groupId,

    -- * Destructuring the Response
    ResetDeploymentsResponse (..),
    newResetDeploymentsResponse,

    -- * Response Lenses
    resetDeploymentsResponse_deploymentArn,
    resetDeploymentsResponse_deploymentId,
    resetDeploymentsResponse_httpStatus,
  )
where

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

-- | Information needed to reset deployments.
--
-- /See:/ 'newResetDeployments' smart constructor.
data ResetDeployments = ResetDeployments'
  { -- | A client token used to correlate requests and responses.
    ResetDeployments -> Maybe Text
amznClientToken :: Prelude.Maybe Prelude.Text,
    -- | If true, performs a best-effort only core reset.
    ResetDeployments -> Maybe Bool
force :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the Greengrass group.
    ResetDeployments -> Text
groupId :: Prelude.Text
  }
  deriving (ResetDeployments -> ResetDeployments -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResetDeployments -> ResetDeployments -> Bool
$c/= :: ResetDeployments -> ResetDeployments -> Bool
== :: ResetDeployments -> ResetDeployments -> Bool
$c== :: ResetDeployments -> ResetDeployments -> Bool
Prelude.Eq, ReadPrec [ResetDeployments]
ReadPrec ResetDeployments
Int -> ReadS ResetDeployments
ReadS [ResetDeployments]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ResetDeployments]
$creadListPrec :: ReadPrec [ResetDeployments]
readPrec :: ReadPrec ResetDeployments
$creadPrec :: ReadPrec ResetDeployments
readList :: ReadS [ResetDeployments]
$creadList :: ReadS [ResetDeployments]
readsPrec :: Int -> ReadS ResetDeployments
$creadsPrec :: Int -> ReadS ResetDeployments
Prelude.Read, Int -> ResetDeployments -> ShowS
[ResetDeployments] -> ShowS
ResetDeployments -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResetDeployments] -> ShowS
$cshowList :: [ResetDeployments] -> ShowS
show :: ResetDeployments -> String
$cshow :: ResetDeployments -> String
showsPrec :: Int -> ResetDeployments -> ShowS
$cshowsPrec :: Int -> ResetDeployments -> ShowS
Prelude.Show, forall x. Rep ResetDeployments x -> ResetDeployments
forall x. ResetDeployments -> Rep ResetDeployments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ResetDeployments x -> ResetDeployments
$cfrom :: forall x. ResetDeployments -> Rep ResetDeployments x
Prelude.Generic)

-- |
-- Create a value of 'ResetDeployments' 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:
--
-- 'amznClientToken', 'resetDeployments_amznClientToken' - A client token used to correlate requests and responses.
--
-- 'force', 'resetDeployments_force' - If true, performs a best-effort only core reset.
--
-- 'groupId', 'resetDeployments_groupId' - The ID of the Greengrass group.
newResetDeployments ::
  -- | 'groupId'
  Prelude.Text ->
  ResetDeployments
newResetDeployments :: Text -> ResetDeployments
newResetDeployments Text
pGroupId_ =
  ResetDeployments'
    { $sel:amznClientToken:ResetDeployments' :: Maybe Text
amznClientToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:force:ResetDeployments' :: Maybe Bool
force = forall a. Maybe a
Prelude.Nothing,
      $sel:groupId:ResetDeployments' :: Text
groupId = Text
pGroupId_
    }

-- | A client token used to correlate requests and responses.
resetDeployments_amznClientToken :: Lens.Lens' ResetDeployments (Prelude.Maybe Prelude.Text)
resetDeployments_amznClientToken :: Lens' ResetDeployments (Maybe Text)
resetDeployments_amznClientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResetDeployments' {Maybe Text
amznClientToken :: Maybe Text
$sel:amznClientToken:ResetDeployments' :: ResetDeployments -> Maybe Text
amznClientToken} -> Maybe Text
amznClientToken) (\s :: ResetDeployments
s@ResetDeployments' {} Maybe Text
a -> ResetDeployments
s {$sel:amznClientToken:ResetDeployments' :: Maybe Text
amznClientToken = Maybe Text
a} :: ResetDeployments)

-- | If true, performs a best-effort only core reset.
resetDeployments_force :: Lens.Lens' ResetDeployments (Prelude.Maybe Prelude.Bool)
resetDeployments_force :: Lens' ResetDeployments (Maybe Bool)
resetDeployments_force = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResetDeployments' {Maybe Bool
force :: Maybe Bool
$sel:force:ResetDeployments' :: ResetDeployments -> Maybe Bool
force} -> Maybe Bool
force) (\s :: ResetDeployments
s@ResetDeployments' {} Maybe Bool
a -> ResetDeployments
s {$sel:force:ResetDeployments' :: Maybe Bool
force = Maybe Bool
a} :: ResetDeployments)

-- | The ID of the Greengrass group.
resetDeployments_groupId :: Lens.Lens' ResetDeployments Prelude.Text
resetDeployments_groupId :: Lens' ResetDeployments Text
resetDeployments_groupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResetDeployments' {Text
groupId :: Text
$sel:groupId:ResetDeployments' :: ResetDeployments -> Text
groupId} -> Text
groupId) (\s :: ResetDeployments
s@ResetDeployments' {} Text
a -> ResetDeployments
s {$sel:groupId:ResetDeployments' :: Text
groupId = Text
a} :: ResetDeployments)

instance Core.AWSRequest ResetDeployments where
  type
    AWSResponse ResetDeployments =
      ResetDeploymentsResponse
  request :: (Service -> Service)
-> ResetDeployments -> Request ResetDeployments
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 ResetDeployments
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ResetDeployments)))
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 -> Int -> ResetDeploymentsResponse
ResetDeploymentsResponse'
            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
"DeploymentArn")
            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
"DeploymentId")
            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 ResetDeployments where
  hashWithSalt :: Int -> ResetDeployments -> Int
hashWithSalt Int
_salt ResetDeployments' {Maybe Bool
Maybe Text
Text
groupId :: Text
force :: Maybe Bool
amznClientToken :: Maybe Text
$sel:groupId:ResetDeployments' :: ResetDeployments -> Text
$sel:force:ResetDeployments' :: ResetDeployments -> Maybe Bool
$sel:amznClientToken:ResetDeployments' :: ResetDeployments -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
amznClientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
force
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
groupId

instance Prelude.NFData ResetDeployments where
  rnf :: ResetDeployments -> ()
rnf ResetDeployments' {Maybe Bool
Maybe Text
Text
groupId :: Text
force :: Maybe Bool
amznClientToken :: Maybe Text
$sel:groupId:ResetDeployments' :: ResetDeployments -> Text
$sel:force:ResetDeployments' :: ResetDeployments -> Maybe Bool
$sel:amznClientToken:ResetDeployments' :: ResetDeployments -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
amznClientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
force
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
groupId

instance Data.ToHeaders ResetDeployments where
  toHeaders :: ResetDeployments -> ResponseHeaders
toHeaders ResetDeployments' {Maybe Bool
Maybe Text
Text
groupId :: Text
force :: Maybe Bool
amznClientToken :: Maybe Text
$sel:groupId:ResetDeployments' :: ResetDeployments -> Text
$sel:force:ResetDeployments' :: ResetDeployments -> Maybe Bool
$sel:amznClientToken:ResetDeployments' :: ResetDeployments -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ HeaderName
"X-Amzn-Client-Token" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
amznClientToken,
        HeaderName
"Content-Type"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# (ByteString
"application/x-amz-json-1.1" :: Prelude.ByteString)
      ]

instance Data.ToJSON ResetDeployments where
  toJSON :: ResetDeployments -> Value
toJSON ResetDeployments' {Maybe Bool
Maybe Text
Text
groupId :: Text
force :: Maybe Bool
amznClientToken :: Maybe Text
$sel:groupId:ResetDeployments' :: ResetDeployments -> Text
$sel:force:ResetDeployments' :: ResetDeployments -> Maybe Bool
$sel:amznClientToken:ResetDeployments' :: ResetDeployments -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [(Key
"Force" 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 Bool
force]
      )

instance Data.ToPath ResetDeployments where
  toPath :: ResetDeployments -> ByteString
toPath ResetDeployments' {Maybe Bool
Maybe Text
Text
groupId :: Text
force :: Maybe Bool
amznClientToken :: Maybe Text
$sel:groupId:ResetDeployments' :: ResetDeployments -> Text
$sel:force:ResetDeployments' :: ResetDeployments -> Maybe Bool
$sel:amznClientToken:ResetDeployments' :: ResetDeployments -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/greengrass/groups/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
groupId,
        ByteString
"/deployments/$reset"
      ]

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

-- | /See:/ 'newResetDeploymentsResponse' smart constructor.
data ResetDeploymentsResponse = ResetDeploymentsResponse'
  { -- | The ARN of the deployment.
    ResetDeploymentsResponse -> Maybe Text
deploymentArn :: Prelude.Maybe Prelude.Text,
    -- | The ID of the deployment.
    ResetDeploymentsResponse -> Maybe Text
deploymentId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ResetDeploymentsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ResetDeploymentsResponse -> ResetDeploymentsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResetDeploymentsResponse -> ResetDeploymentsResponse -> Bool
$c/= :: ResetDeploymentsResponse -> ResetDeploymentsResponse -> Bool
== :: ResetDeploymentsResponse -> ResetDeploymentsResponse -> Bool
$c== :: ResetDeploymentsResponse -> ResetDeploymentsResponse -> Bool
Prelude.Eq, ReadPrec [ResetDeploymentsResponse]
ReadPrec ResetDeploymentsResponse
Int -> ReadS ResetDeploymentsResponse
ReadS [ResetDeploymentsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ResetDeploymentsResponse]
$creadListPrec :: ReadPrec [ResetDeploymentsResponse]
readPrec :: ReadPrec ResetDeploymentsResponse
$creadPrec :: ReadPrec ResetDeploymentsResponse
readList :: ReadS [ResetDeploymentsResponse]
$creadList :: ReadS [ResetDeploymentsResponse]
readsPrec :: Int -> ReadS ResetDeploymentsResponse
$creadsPrec :: Int -> ReadS ResetDeploymentsResponse
Prelude.Read, Int -> ResetDeploymentsResponse -> ShowS
[ResetDeploymentsResponse] -> ShowS
ResetDeploymentsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResetDeploymentsResponse] -> ShowS
$cshowList :: [ResetDeploymentsResponse] -> ShowS
show :: ResetDeploymentsResponse -> String
$cshow :: ResetDeploymentsResponse -> String
showsPrec :: Int -> ResetDeploymentsResponse -> ShowS
$cshowsPrec :: Int -> ResetDeploymentsResponse -> ShowS
Prelude.Show, forall x.
Rep ResetDeploymentsResponse x -> ResetDeploymentsResponse
forall x.
ResetDeploymentsResponse -> Rep ResetDeploymentsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ResetDeploymentsResponse x -> ResetDeploymentsResponse
$cfrom :: forall x.
ResetDeploymentsResponse -> Rep ResetDeploymentsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ResetDeploymentsResponse' 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:
--
-- 'deploymentArn', 'resetDeploymentsResponse_deploymentArn' - The ARN of the deployment.
--
-- 'deploymentId', 'resetDeploymentsResponse_deploymentId' - The ID of the deployment.
--
-- 'httpStatus', 'resetDeploymentsResponse_httpStatus' - The response's http status code.
newResetDeploymentsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ResetDeploymentsResponse
newResetDeploymentsResponse :: Int -> ResetDeploymentsResponse
newResetDeploymentsResponse Int
pHttpStatus_ =
  ResetDeploymentsResponse'
    { $sel:deploymentArn:ResetDeploymentsResponse' :: Maybe Text
deploymentArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:deploymentId:ResetDeploymentsResponse' :: Maybe Text
deploymentId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ResetDeploymentsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ARN of the deployment.
resetDeploymentsResponse_deploymentArn :: Lens.Lens' ResetDeploymentsResponse (Prelude.Maybe Prelude.Text)
resetDeploymentsResponse_deploymentArn :: Lens' ResetDeploymentsResponse (Maybe Text)
resetDeploymentsResponse_deploymentArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResetDeploymentsResponse' {Maybe Text
deploymentArn :: Maybe Text
$sel:deploymentArn:ResetDeploymentsResponse' :: ResetDeploymentsResponse -> Maybe Text
deploymentArn} -> Maybe Text
deploymentArn) (\s :: ResetDeploymentsResponse
s@ResetDeploymentsResponse' {} Maybe Text
a -> ResetDeploymentsResponse
s {$sel:deploymentArn:ResetDeploymentsResponse' :: Maybe Text
deploymentArn = Maybe Text
a} :: ResetDeploymentsResponse)

-- | The ID of the deployment.
resetDeploymentsResponse_deploymentId :: Lens.Lens' ResetDeploymentsResponse (Prelude.Maybe Prelude.Text)
resetDeploymentsResponse_deploymentId :: Lens' ResetDeploymentsResponse (Maybe Text)
resetDeploymentsResponse_deploymentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResetDeploymentsResponse' {Maybe Text
deploymentId :: Maybe Text
$sel:deploymentId:ResetDeploymentsResponse' :: ResetDeploymentsResponse -> Maybe Text
deploymentId} -> Maybe Text
deploymentId) (\s :: ResetDeploymentsResponse
s@ResetDeploymentsResponse' {} Maybe Text
a -> ResetDeploymentsResponse
s {$sel:deploymentId:ResetDeploymentsResponse' :: Maybe Text
deploymentId = Maybe Text
a} :: ResetDeploymentsResponse)

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

instance Prelude.NFData ResetDeploymentsResponse where
  rnf :: ResetDeploymentsResponse -> ()
rnf ResetDeploymentsResponse' {Int
Maybe Text
httpStatus :: Int
deploymentId :: Maybe Text
deploymentArn :: Maybe Text
$sel:httpStatus:ResetDeploymentsResponse' :: ResetDeploymentsResponse -> Int
$sel:deploymentId:ResetDeploymentsResponse' :: ResetDeploymentsResponse -> Maybe Text
$sel:deploymentArn:ResetDeploymentsResponse' :: ResetDeploymentsResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
deploymentArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
deploymentId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus