{-# 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.SSM.ResetServiceSetting
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- @ServiceSetting@ is an account-level setting for an Amazon Web Services
-- service. This setting defines how a user interacts with or uses a
-- service or a feature of a service. For example, if an Amazon Web
-- Services service charges money to the account based on feature or
-- service usage, then the Amazon Web Services service team might create a
-- default setting of \"false\". This means the user can\'t use this
-- feature unless they change the setting to \"true\" and intentionally opt
-- in for a paid feature.
--
-- Services map a @SettingId@ object to a setting value. Amazon Web
-- Services services teams define the default value for a @SettingId@. You
-- can\'t create a new @SettingId@, but you can overwrite the default value
-- if you have the @ssm:UpdateServiceSetting@ permission for the setting.
-- Use the GetServiceSetting API operation to view the current value. Use
-- the UpdateServiceSetting API operation to change the default setting.
--
-- Reset the service setting for the account to the default value as
-- provisioned by the Amazon Web Services service team.
module Amazonka.SSM.ResetServiceSetting
  ( -- * Creating a Request
    ResetServiceSetting (..),
    newResetServiceSetting,

    -- * Request Lenses
    resetServiceSetting_settingId,

    -- * Destructuring the Response
    ResetServiceSettingResponse (..),
    newResetServiceSettingResponse,

    -- * Response Lenses
    resetServiceSettingResponse_serviceSetting,
    resetServiceSettingResponse_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.SSM.Types

-- | The request body of the ResetServiceSetting API operation.
--
-- /See:/ 'newResetServiceSetting' smart constructor.
data ResetServiceSetting = ResetServiceSetting'
  { -- | The Amazon Resource Name (ARN) of the service setting to reset. The
    -- setting ID can be one of the following.
    --
    -- -   @\/ssm\/automation\/customer-script-log-destination@
    --
    -- -   @\/ssm\/automation\/customer-script-log-group-name@
    --
    -- -   @\/ssm\/documents\/console\/public-sharing-permission@
    --
    -- -   @\/ssm\/managed-instance\/activation-tier@
    --
    -- -   @\/ssm\/opsinsights\/opscenter@
    --
    -- -   @\/ssm\/parameter-store\/default-parameter-tier@
    --
    -- -   @\/ssm\/parameter-store\/high-throughput-enabled@
    ResetServiceSetting -> Text
settingId :: Prelude.Text
  }
  deriving (ResetServiceSetting -> ResetServiceSetting -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResetServiceSetting -> ResetServiceSetting -> Bool
$c/= :: ResetServiceSetting -> ResetServiceSetting -> Bool
== :: ResetServiceSetting -> ResetServiceSetting -> Bool
$c== :: ResetServiceSetting -> ResetServiceSetting -> Bool
Prelude.Eq, ReadPrec [ResetServiceSetting]
ReadPrec ResetServiceSetting
Int -> ReadS ResetServiceSetting
ReadS [ResetServiceSetting]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ResetServiceSetting]
$creadListPrec :: ReadPrec [ResetServiceSetting]
readPrec :: ReadPrec ResetServiceSetting
$creadPrec :: ReadPrec ResetServiceSetting
readList :: ReadS [ResetServiceSetting]
$creadList :: ReadS [ResetServiceSetting]
readsPrec :: Int -> ReadS ResetServiceSetting
$creadsPrec :: Int -> ReadS ResetServiceSetting
Prelude.Read, Int -> ResetServiceSetting -> ShowS
[ResetServiceSetting] -> ShowS
ResetServiceSetting -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResetServiceSetting] -> ShowS
$cshowList :: [ResetServiceSetting] -> ShowS
show :: ResetServiceSetting -> String
$cshow :: ResetServiceSetting -> String
showsPrec :: Int -> ResetServiceSetting -> ShowS
$cshowsPrec :: Int -> ResetServiceSetting -> ShowS
Prelude.Show, forall x. Rep ResetServiceSetting x -> ResetServiceSetting
forall x. ResetServiceSetting -> Rep ResetServiceSetting x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ResetServiceSetting x -> ResetServiceSetting
$cfrom :: forall x. ResetServiceSetting -> Rep ResetServiceSetting x
Prelude.Generic)

-- |
-- Create a value of 'ResetServiceSetting' 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:
--
-- 'settingId', 'resetServiceSetting_settingId' - The Amazon Resource Name (ARN) of the service setting to reset. The
-- setting ID can be one of the following.
--
-- -   @\/ssm\/automation\/customer-script-log-destination@
--
-- -   @\/ssm\/automation\/customer-script-log-group-name@
--
-- -   @\/ssm\/documents\/console\/public-sharing-permission@
--
-- -   @\/ssm\/managed-instance\/activation-tier@
--
-- -   @\/ssm\/opsinsights\/opscenter@
--
-- -   @\/ssm\/parameter-store\/default-parameter-tier@
--
-- -   @\/ssm\/parameter-store\/high-throughput-enabled@
newResetServiceSetting ::
  -- | 'settingId'
  Prelude.Text ->
  ResetServiceSetting
newResetServiceSetting :: Text -> ResetServiceSetting
newResetServiceSetting Text
pSettingId_ =
  ResetServiceSetting' {$sel:settingId:ResetServiceSetting' :: Text
settingId = Text
pSettingId_}

-- | The Amazon Resource Name (ARN) of the service setting to reset. The
-- setting ID can be one of the following.
--
-- -   @\/ssm\/automation\/customer-script-log-destination@
--
-- -   @\/ssm\/automation\/customer-script-log-group-name@
--
-- -   @\/ssm\/documents\/console\/public-sharing-permission@
--
-- -   @\/ssm\/managed-instance\/activation-tier@
--
-- -   @\/ssm\/opsinsights\/opscenter@
--
-- -   @\/ssm\/parameter-store\/default-parameter-tier@
--
-- -   @\/ssm\/parameter-store\/high-throughput-enabled@
resetServiceSetting_settingId :: Lens.Lens' ResetServiceSetting Prelude.Text
resetServiceSetting_settingId :: Lens' ResetServiceSetting Text
resetServiceSetting_settingId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResetServiceSetting' {Text
settingId :: Text
$sel:settingId:ResetServiceSetting' :: ResetServiceSetting -> Text
settingId} -> Text
settingId) (\s :: ResetServiceSetting
s@ResetServiceSetting' {} Text
a -> ResetServiceSetting
s {$sel:settingId:ResetServiceSetting' :: Text
settingId = Text
a} :: ResetServiceSetting)

instance Core.AWSRequest ResetServiceSetting where
  type
    AWSResponse ResetServiceSetting =
      ResetServiceSettingResponse
  request :: (Service -> Service)
-> ResetServiceSetting -> Request ResetServiceSetting
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 ResetServiceSetting
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ResetServiceSetting)))
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 ServiceSetting -> Int -> ResetServiceSettingResponse
ResetServiceSettingResponse'
            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
"ServiceSetting")
            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 ResetServiceSetting where
  hashWithSalt :: Int -> ResetServiceSetting -> Int
hashWithSalt Int
_salt ResetServiceSetting' {Text
settingId :: Text
$sel:settingId:ResetServiceSetting' :: ResetServiceSetting -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
settingId

instance Prelude.NFData ResetServiceSetting where
  rnf :: ResetServiceSetting -> ()
rnf ResetServiceSetting' {Text
settingId :: Text
$sel:settingId:ResetServiceSetting' :: ResetServiceSetting -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
settingId

instance Data.ToHeaders ResetServiceSetting where
  toHeaders :: ResetServiceSetting -> 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
"AmazonSSM.ResetServiceSetting" ::
                          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 ResetServiceSetting where
  toJSON :: ResetServiceSetting -> Value
toJSON ResetServiceSetting' {Text
settingId :: Text
$sel:settingId:ResetServiceSetting' :: ResetServiceSetting -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"SettingId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
settingId)]
      )

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

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

-- | The result body of the ResetServiceSetting API operation.
--
-- /See:/ 'newResetServiceSettingResponse' smart constructor.
data ResetServiceSettingResponse = ResetServiceSettingResponse'
  { -- | The current, effective service setting after calling the
    -- ResetServiceSetting API operation.
    ResetServiceSettingResponse -> Maybe ServiceSetting
serviceSetting :: Prelude.Maybe ServiceSetting,
    -- | The response's http status code.
    ResetServiceSettingResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ResetServiceSettingResponse -> ResetServiceSettingResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResetServiceSettingResponse -> ResetServiceSettingResponse -> Bool
$c/= :: ResetServiceSettingResponse -> ResetServiceSettingResponse -> Bool
== :: ResetServiceSettingResponse -> ResetServiceSettingResponse -> Bool
$c== :: ResetServiceSettingResponse -> ResetServiceSettingResponse -> Bool
Prelude.Eq, ReadPrec [ResetServiceSettingResponse]
ReadPrec ResetServiceSettingResponse
Int -> ReadS ResetServiceSettingResponse
ReadS [ResetServiceSettingResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ResetServiceSettingResponse]
$creadListPrec :: ReadPrec [ResetServiceSettingResponse]
readPrec :: ReadPrec ResetServiceSettingResponse
$creadPrec :: ReadPrec ResetServiceSettingResponse
readList :: ReadS [ResetServiceSettingResponse]
$creadList :: ReadS [ResetServiceSettingResponse]
readsPrec :: Int -> ReadS ResetServiceSettingResponse
$creadsPrec :: Int -> ReadS ResetServiceSettingResponse
Prelude.Read, Int -> ResetServiceSettingResponse -> ShowS
[ResetServiceSettingResponse] -> ShowS
ResetServiceSettingResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResetServiceSettingResponse] -> ShowS
$cshowList :: [ResetServiceSettingResponse] -> ShowS
show :: ResetServiceSettingResponse -> String
$cshow :: ResetServiceSettingResponse -> String
showsPrec :: Int -> ResetServiceSettingResponse -> ShowS
$cshowsPrec :: Int -> ResetServiceSettingResponse -> ShowS
Prelude.Show, forall x.
Rep ResetServiceSettingResponse x -> ResetServiceSettingResponse
forall x.
ResetServiceSettingResponse -> Rep ResetServiceSettingResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ResetServiceSettingResponse x -> ResetServiceSettingResponse
$cfrom :: forall x.
ResetServiceSettingResponse -> Rep ResetServiceSettingResponse x
Prelude.Generic)

-- |
-- Create a value of 'ResetServiceSettingResponse' 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:
--
-- 'serviceSetting', 'resetServiceSettingResponse_serviceSetting' - The current, effective service setting after calling the
-- ResetServiceSetting API operation.
--
-- 'httpStatus', 'resetServiceSettingResponse_httpStatus' - The response's http status code.
newResetServiceSettingResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ResetServiceSettingResponse
newResetServiceSettingResponse :: Int -> ResetServiceSettingResponse
newResetServiceSettingResponse Int
pHttpStatus_ =
  ResetServiceSettingResponse'
    { $sel:serviceSetting:ResetServiceSettingResponse' :: Maybe ServiceSetting
serviceSetting =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ResetServiceSettingResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The current, effective service setting after calling the
-- ResetServiceSetting API operation.
resetServiceSettingResponse_serviceSetting :: Lens.Lens' ResetServiceSettingResponse (Prelude.Maybe ServiceSetting)
resetServiceSettingResponse_serviceSetting :: Lens' ResetServiceSettingResponse (Maybe ServiceSetting)
resetServiceSettingResponse_serviceSetting = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResetServiceSettingResponse' {Maybe ServiceSetting
serviceSetting :: Maybe ServiceSetting
$sel:serviceSetting:ResetServiceSettingResponse' :: ResetServiceSettingResponse -> Maybe ServiceSetting
serviceSetting} -> Maybe ServiceSetting
serviceSetting) (\s :: ResetServiceSettingResponse
s@ResetServiceSettingResponse' {} Maybe ServiceSetting
a -> ResetServiceSettingResponse
s {$sel:serviceSetting:ResetServiceSettingResponse' :: Maybe ServiceSetting
serviceSetting = Maybe ServiceSetting
a} :: ResetServiceSettingResponse)

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

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