{-# 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.Grafana.UpdateWorkspaceConfiguration
-- 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 the configuration string for the given workspace
module Amazonka.Grafana.UpdateWorkspaceConfiguration
  ( -- * Creating a Request
    UpdateWorkspaceConfiguration (..),
    newUpdateWorkspaceConfiguration,

    -- * Request Lenses
    updateWorkspaceConfiguration_configuration,
    updateWorkspaceConfiguration_workspaceId,

    -- * Destructuring the Response
    UpdateWorkspaceConfigurationResponse (..),
    newUpdateWorkspaceConfigurationResponse,

    -- * Response Lenses
    updateWorkspaceConfigurationResponse_httpStatus,
  )
where

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

-- | /See:/ 'newUpdateWorkspaceConfiguration' smart constructor.
data UpdateWorkspaceConfiguration = UpdateWorkspaceConfiguration'
  { -- | The new configuration string for the workspace. For more information
    -- about the format and configuration options available, see
    -- <https://docs.aws.amazon.com/grafana/latest/userguide/AMG-configure-workspace.html Working in your Grafana workspace>.
    UpdateWorkspaceConfiguration -> Text
configuration :: Prelude.Text,
    -- | The ID of the workspace to update.
    UpdateWorkspaceConfiguration -> Text
workspaceId :: Prelude.Text
  }
  deriving (UpdateWorkspaceConfiguration
-> UpdateWorkspaceConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateWorkspaceConfiguration
-> UpdateWorkspaceConfiguration -> Bool
$c/= :: UpdateWorkspaceConfiguration
-> UpdateWorkspaceConfiguration -> Bool
== :: UpdateWorkspaceConfiguration
-> UpdateWorkspaceConfiguration -> Bool
$c== :: UpdateWorkspaceConfiguration
-> UpdateWorkspaceConfiguration -> Bool
Prelude.Eq, ReadPrec [UpdateWorkspaceConfiguration]
ReadPrec UpdateWorkspaceConfiguration
Int -> ReadS UpdateWorkspaceConfiguration
ReadS [UpdateWorkspaceConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateWorkspaceConfiguration]
$creadListPrec :: ReadPrec [UpdateWorkspaceConfiguration]
readPrec :: ReadPrec UpdateWorkspaceConfiguration
$creadPrec :: ReadPrec UpdateWorkspaceConfiguration
readList :: ReadS [UpdateWorkspaceConfiguration]
$creadList :: ReadS [UpdateWorkspaceConfiguration]
readsPrec :: Int -> ReadS UpdateWorkspaceConfiguration
$creadsPrec :: Int -> ReadS UpdateWorkspaceConfiguration
Prelude.Read, Int -> UpdateWorkspaceConfiguration -> ShowS
[UpdateWorkspaceConfiguration] -> ShowS
UpdateWorkspaceConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateWorkspaceConfiguration] -> ShowS
$cshowList :: [UpdateWorkspaceConfiguration] -> ShowS
show :: UpdateWorkspaceConfiguration -> String
$cshow :: UpdateWorkspaceConfiguration -> String
showsPrec :: Int -> UpdateWorkspaceConfiguration -> ShowS
$cshowsPrec :: Int -> UpdateWorkspaceConfiguration -> ShowS
Prelude.Show, forall x.
Rep UpdateWorkspaceConfiguration x -> UpdateWorkspaceConfiguration
forall x.
UpdateWorkspaceConfiguration -> Rep UpdateWorkspaceConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateWorkspaceConfiguration x -> UpdateWorkspaceConfiguration
$cfrom :: forall x.
UpdateWorkspaceConfiguration -> Rep UpdateWorkspaceConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'UpdateWorkspaceConfiguration' 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:
--
-- 'configuration', 'updateWorkspaceConfiguration_configuration' - The new configuration string for the workspace. For more information
-- about the format and configuration options available, see
-- <https://docs.aws.amazon.com/grafana/latest/userguide/AMG-configure-workspace.html Working in your Grafana workspace>.
--
-- 'workspaceId', 'updateWorkspaceConfiguration_workspaceId' - The ID of the workspace to update.
newUpdateWorkspaceConfiguration ::
  -- | 'configuration'
  Prelude.Text ->
  -- | 'workspaceId'
  Prelude.Text ->
  UpdateWorkspaceConfiguration
newUpdateWorkspaceConfiguration :: Text -> Text -> UpdateWorkspaceConfiguration
newUpdateWorkspaceConfiguration
  Text
pConfiguration_
  Text
pWorkspaceId_ =
    UpdateWorkspaceConfiguration'
      { $sel:configuration:UpdateWorkspaceConfiguration' :: Text
configuration =
          Text
pConfiguration_,
        $sel:workspaceId:UpdateWorkspaceConfiguration' :: Text
workspaceId = Text
pWorkspaceId_
      }

-- | The new configuration string for the workspace. For more information
-- about the format and configuration options available, see
-- <https://docs.aws.amazon.com/grafana/latest/userguide/AMG-configure-workspace.html Working in your Grafana workspace>.
updateWorkspaceConfiguration_configuration :: Lens.Lens' UpdateWorkspaceConfiguration Prelude.Text
updateWorkspaceConfiguration_configuration :: Lens' UpdateWorkspaceConfiguration Text
updateWorkspaceConfiguration_configuration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkspaceConfiguration' {Text
configuration :: Text
$sel:configuration:UpdateWorkspaceConfiguration' :: UpdateWorkspaceConfiguration -> Text
configuration} -> Text
configuration) (\s :: UpdateWorkspaceConfiguration
s@UpdateWorkspaceConfiguration' {} Text
a -> UpdateWorkspaceConfiguration
s {$sel:configuration:UpdateWorkspaceConfiguration' :: Text
configuration = Text
a} :: UpdateWorkspaceConfiguration)

-- | The ID of the workspace to update.
updateWorkspaceConfiguration_workspaceId :: Lens.Lens' UpdateWorkspaceConfiguration Prelude.Text
updateWorkspaceConfiguration_workspaceId :: Lens' UpdateWorkspaceConfiguration Text
updateWorkspaceConfiguration_workspaceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkspaceConfiguration' {Text
workspaceId :: Text
$sel:workspaceId:UpdateWorkspaceConfiguration' :: UpdateWorkspaceConfiguration -> Text
workspaceId} -> Text
workspaceId) (\s :: UpdateWorkspaceConfiguration
s@UpdateWorkspaceConfiguration' {} Text
a -> UpdateWorkspaceConfiguration
s {$sel:workspaceId:UpdateWorkspaceConfiguration' :: Text
workspaceId = Text
a} :: UpdateWorkspaceConfiguration)

instance Core.AWSRequest UpdateWorkspaceConfiguration where
  type
    AWSResponse UpdateWorkspaceConfiguration =
      UpdateWorkspaceConfigurationResponse
  request :: (Service -> Service)
-> UpdateWorkspaceConfiguration
-> Request UpdateWorkspaceConfiguration
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateWorkspaceConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateWorkspaceConfiguration)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> UpdateWorkspaceConfigurationResponse
UpdateWorkspaceConfigurationResponse'
            forall (f :: * -> *) a b. Functor 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
    UpdateWorkspaceConfiguration
  where
  hashWithSalt :: Int -> UpdateWorkspaceConfiguration -> Int
hashWithSalt Int
_salt UpdateWorkspaceConfiguration' {Text
workspaceId :: Text
configuration :: Text
$sel:workspaceId:UpdateWorkspaceConfiguration' :: UpdateWorkspaceConfiguration -> Text
$sel:configuration:UpdateWorkspaceConfiguration' :: UpdateWorkspaceConfiguration -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
configuration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
workspaceId

instance Prelude.NFData UpdateWorkspaceConfiguration where
  rnf :: UpdateWorkspaceConfiguration -> ()
rnf UpdateWorkspaceConfiguration' {Text
workspaceId :: Text
configuration :: Text
$sel:workspaceId:UpdateWorkspaceConfiguration' :: UpdateWorkspaceConfiguration -> Text
$sel:configuration:UpdateWorkspaceConfiguration' :: UpdateWorkspaceConfiguration -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
configuration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
workspaceId

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

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

instance Data.ToPath UpdateWorkspaceConfiguration where
  toPath :: UpdateWorkspaceConfiguration -> ByteString
toPath UpdateWorkspaceConfiguration' {Text
workspaceId :: Text
configuration :: Text
$sel:workspaceId:UpdateWorkspaceConfiguration' :: UpdateWorkspaceConfiguration -> Text
$sel:configuration:UpdateWorkspaceConfiguration' :: UpdateWorkspaceConfiguration -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/workspaces/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
workspaceId,
        ByteString
"/configuration"
      ]

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

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

-- |
-- Create a value of 'UpdateWorkspaceConfigurationResponse' 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:
--
-- 'httpStatus', 'updateWorkspaceConfigurationResponse_httpStatus' - The response's http status code.
newUpdateWorkspaceConfigurationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateWorkspaceConfigurationResponse
newUpdateWorkspaceConfigurationResponse :: Int -> UpdateWorkspaceConfigurationResponse
newUpdateWorkspaceConfigurationResponse Int
pHttpStatus_ =
  UpdateWorkspaceConfigurationResponse'
    { $sel:httpStatus:UpdateWorkspaceConfigurationResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

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

instance
  Prelude.NFData
    UpdateWorkspaceConfigurationResponse
  where
  rnf :: UpdateWorkspaceConfigurationResponse -> ()
rnf UpdateWorkspaceConfigurationResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateWorkspaceConfigurationResponse' :: UpdateWorkspaceConfigurationResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus