{-# 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.GetServiceSetting
-- 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 UpdateServiceSetting API operation to change the default
-- setting. Or use the ResetServiceSetting to change the value back to the
-- original value defined by the Amazon Web Services service team.
--
-- Query the current service setting for the Amazon Web Services account.
module Amazonka.SSM.GetServiceSetting
  ( -- * Creating a Request
    GetServiceSetting (..),
    newGetServiceSetting,

    -- * Request Lenses
    getServiceSetting_settingId,

    -- * Destructuring the Response
    GetServiceSettingResponse (..),
    newGetServiceSettingResponse,

    -- * Response Lenses
    getServiceSettingResponse_serviceSetting,
    getServiceSettingResponse_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 GetServiceSetting API operation.
--
-- /See:/ 'newGetServiceSetting' smart constructor.
data GetServiceSetting = GetServiceSetting'
  { -- | The ID of the service setting to get. 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@
    GetServiceSetting -> Text
settingId :: Prelude.Text
  }
  deriving (GetServiceSetting -> GetServiceSetting -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetServiceSetting -> GetServiceSetting -> Bool
$c/= :: GetServiceSetting -> GetServiceSetting -> Bool
== :: GetServiceSetting -> GetServiceSetting -> Bool
$c== :: GetServiceSetting -> GetServiceSetting -> Bool
Prelude.Eq, ReadPrec [GetServiceSetting]
ReadPrec GetServiceSetting
Int -> ReadS GetServiceSetting
ReadS [GetServiceSetting]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetServiceSetting]
$creadListPrec :: ReadPrec [GetServiceSetting]
readPrec :: ReadPrec GetServiceSetting
$creadPrec :: ReadPrec GetServiceSetting
readList :: ReadS [GetServiceSetting]
$creadList :: ReadS [GetServiceSetting]
readsPrec :: Int -> ReadS GetServiceSetting
$creadsPrec :: Int -> ReadS GetServiceSetting
Prelude.Read, Int -> GetServiceSetting -> ShowS
[GetServiceSetting] -> ShowS
GetServiceSetting -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetServiceSetting] -> ShowS
$cshowList :: [GetServiceSetting] -> ShowS
show :: GetServiceSetting -> String
$cshow :: GetServiceSetting -> String
showsPrec :: Int -> GetServiceSetting -> ShowS
$cshowsPrec :: Int -> GetServiceSetting -> ShowS
Prelude.Show, forall x. Rep GetServiceSetting x -> GetServiceSetting
forall x. GetServiceSetting -> Rep GetServiceSetting x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetServiceSetting x -> GetServiceSetting
$cfrom :: forall x. GetServiceSetting -> Rep GetServiceSetting x
Prelude.Generic)

-- |
-- Create a value of 'GetServiceSetting' 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', 'getServiceSetting_settingId' - The ID of the service setting to get. 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@
newGetServiceSetting ::
  -- | 'settingId'
  Prelude.Text ->
  GetServiceSetting
newGetServiceSetting :: Text -> GetServiceSetting
newGetServiceSetting Text
pSettingId_ =
  GetServiceSetting' {$sel:settingId:GetServiceSetting' :: Text
settingId = Text
pSettingId_}

-- | The ID of the service setting to get. 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@
getServiceSetting_settingId :: Lens.Lens' GetServiceSetting Prelude.Text
getServiceSetting_settingId :: Lens' GetServiceSetting Text
getServiceSetting_settingId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceSetting' {Text
settingId :: Text
$sel:settingId:GetServiceSetting' :: GetServiceSetting -> Text
settingId} -> Text
settingId) (\s :: GetServiceSetting
s@GetServiceSetting' {} Text
a -> GetServiceSetting
s {$sel:settingId:GetServiceSetting' :: Text
settingId = Text
a} :: GetServiceSetting)

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

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

instance Data.ToHeaders GetServiceSetting where
  toHeaders :: GetServiceSetting -> 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.GetServiceSetting" ::
                          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 GetServiceSetting where
  toJSON :: GetServiceSetting -> Value
toJSON GetServiceSetting' {Text
settingId :: Text
$sel:settingId:GetServiceSetting' :: GetServiceSetting -> 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 GetServiceSetting where
  toPath :: GetServiceSetting -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

-- |
-- Create a value of 'GetServiceSettingResponse' 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', 'getServiceSettingResponse_serviceSetting' - The query result of the current service setting.
--
-- 'httpStatus', 'getServiceSettingResponse_httpStatus' - The response's http status code.
newGetServiceSettingResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetServiceSettingResponse
newGetServiceSettingResponse :: Int -> GetServiceSettingResponse
newGetServiceSettingResponse Int
pHttpStatus_ =
  GetServiceSettingResponse'
    { $sel:serviceSetting:GetServiceSettingResponse' :: Maybe ServiceSetting
serviceSetting =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetServiceSettingResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The query result of the current service setting.
getServiceSettingResponse_serviceSetting :: Lens.Lens' GetServiceSettingResponse (Prelude.Maybe ServiceSetting)
getServiceSettingResponse_serviceSetting :: Lens' GetServiceSettingResponse (Maybe ServiceSetting)
getServiceSettingResponse_serviceSetting = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceSettingResponse' {Maybe ServiceSetting
serviceSetting :: Maybe ServiceSetting
$sel:serviceSetting:GetServiceSettingResponse' :: GetServiceSettingResponse -> Maybe ServiceSetting
serviceSetting} -> Maybe ServiceSetting
serviceSetting) (\s :: GetServiceSettingResponse
s@GetServiceSettingResponse' {} Maybe ServiceSetting
a -> GetServiceSettingResponse
s {$sel:serviceSetting:GetServiceSettingResponse' :: Maybe ServiceSetting
serviceSetting = Maybe ServiceSetting
a} :: GetServiceSettingResponse)

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

instance Prelude.NFData GetServiceSettingResponse where
  rnf :: GetServiceSettingResponse -> ()
rnf GetServiceSettingResponse' {Int
Maybe ServiceSetting
httpStatus :: Int
serviceSetting :: Maybe ServiceSetting
$sel:httpStatus:GetServiceSettingResponse' :: GetServiceSettingResponse -> Int
$sel:serviceSetting:GetServiceSettingResponse' :: GetServiceSettingResponse -> 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