{-# 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 #-}
module Amazonka.CloudSearch.UpdateScalingParameters
  ( 
    UpdateScalingParameters (..),
    newUpdateScalingParameters,
    
    updateScalingParameters_domainName,
    updateScalingParameters_scalingParameters,
    
    UpdateScalingParametersResponse (..),
    newUpdateScalingParametersResponse,
    
    updateScalingParametersResponse_httpStatus,
    updateScalingParametersResponse_scalingParameters,
  )
where
import Amazonka.CloudSearch.Types
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
data UpdateScalingParameters = UpdateScalingParameters'
  { UpdateScalingParameters -> Text
domainName :: Prelude.Text,
    UpdateScalingParameters -> ScalingParameters
scalingParameters :: ScalingParameters
  }
  deriving (UpdateScalingParameters -> UpdateScalingParameters -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateScalingParameters -> UpdateScalingParameters -> Bool
$c/= :: UpdateScalingParameters -> UpdateScalingParameters -> Bool
== :: UpdateScalingParameters -> UpdateScalingParameters -> Bool
$c== :: UpdateScalingParameters -> UpdateScalingParameters -> Bool
Prelude.Eq, ReadPrec [UpdateScalingParameters]
ReadPrec UpdateScalingParameters
Int -> ReadS UpdateScalingParameters
ReadS [UpdateScalingParameters]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateScalingParameters]
$creadListPrec :: ReadPrec [UpdateScalingParameters]
readPrec :: ReadPrec UpdateScalingParameters
$creadPrec :: ReadPrec UpdateScalingParameters
readList :: ReadS [UpdateScalingParameters]
$creadList :: ReadS [UpdateScalingParameters]
readsPrec :: Int -> ReadS UpdateScalingParameters
$creadsPrec :: Int -> ReadS UpdateScalingParameters
Prelude.Read, Int -> UpdateScalingParameters -> ShowS
[UpdateScalingParameters] -> ShowS
UpdateScalingParameters -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateScalingParameters] -> ShowS
$cshowList :: [UpdateScalingParameters] -> ShowS
show :: UpdateScalingParameters -> String
$cshow :: UpdateScalingParameters -> String
showsPrec :: Int -> UpdateScalingParameters -> ShowS
$cshowsPrec :: Int -> UpdateScalingParameters -> ShowS
Prelude.Show, forall x. Rep UpdateScalingParameters x -> UpdateScalingParameters
forall x. UpdateScalingParameters -> Rep UpdateScalingParameters x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateScalingParameters x -> UpdateScalingParameters
$cfrom :: forall x. UpdateScalingParameters -> Rep UpdateScalingParameters x
Prelude.Generic)
newUpdateScalingParameters ::
  
  Prelude.Text ->
  
  ScalingParameters ->
  UpdateScalingParameters
newUpdateScalingParameters :: Text -> ScalingParameters -> UpdateScalingParameters
newUpdateScalingParameters
  Text
pDomainName_
  ScalingParameters
pScalingParameters_ =
    UpdateScalingParameters'
      { $sel:domainName:UpdateScalingParameters' :: Text
domainName = Text
pDomainName_,
        $sel:scalingParameters:UpdateScalingParameters' :: ScalingParameters
scalingParameters = ScalingParameters
pScalingParameters_
      }
updateScalingParameters_domainName :: Lens.Lens' UpdateScalingParameters Prelude.Text
updateScalingParameters_domainName :: Lens' UpdateScalingParameters Text
updateScalingParameters_domainName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateScalingParameters' {Text
domainName :: Text
$sel:domainName:UpdateScalingParameters' :: UpdateScalingParameters -> Text
domainName} -> Text
domainName) (\s :: UpdateScalingParameters
s@UpdateScalingParameters' {} Text
a -> UpdateScalingParameters
s {$sel:domainName:UpdateScalingParameters' :: Text
domainName = Text
a} :: UpdateScalingParameters)
updateScalingParameters_scalingParameters :: Lens.Lens' UpdateScalingParameters ScalingParameters
updateScalingParameters_scalingParameters :: Lens' UpdateScalingParameters ScalingParameters
updateScalingParameters_scalingParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateScalingParameters' {ScalingParameters
scalingParameters :: ScalingParameters
$sel:scalingParameters:UpdateScalingParameters' :: UpdateScalingParameters -> ScalingParameters
scalingParameters} -> ScalingParameters
scalingParameters) (\s :: UpdateScalingParameters
s@UpdateScalingParameters' {} ScalingParameters
a -> UpdateScalingParameters
s {$sel:scalingParameters:UpdateScalingParameters' :: ScalingParameters
scalingParameters = ScalingParameters
a} :: UpdateScalingParameters)
instance Core.AWSRequest UpdateScalingParameters where
  type
    AWSResponse UpdateScalingParameters =
      UpdateScalingParametersResponse
  request :: (Service -> Service)
-> UpdateScalingParameters -> Request UpdateScalingParameters
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateScalingParameters
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateScalingParameters)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"UpdateScalingParametersResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int -> ScalingParametersStatus -> UpdateScalingParametersResponse
UpdateScalingParametersResponse'
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"ScalingParameters")
      )
instance Prelude.Hashable UpdateScalingParameters where
  hashWithSalt :: Int -> UpdateScalingParameters -> Int
hashWithSalt Int
_salt UpdateScalingParameters' {Text
ScalingParameters
scalingParameters :: ScalingParameters
domainName :: Text
$sel:scalingParameters:UpdateScalingParameters' :: UpdateScalingParameters -> ScalingParameters
$sel:domainName:UpdateScalingParameters' :: UpdateScalingParameters -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
domainName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ScalingParameters
scalingParameters
instance Prelude.NFData UpdateScalingParameters where
  rnf :: UpdateScalingParameters -> ()
rnf UpdateScalingParameters' {Text
ScalingParameters
scalingParameters :: ScalingParameters
domainName :: Text
$sel:scalingParameters:UpdateScalingParameters' :: UpdateScalingParameters -> ScalingParameters
$sel:domainName:UpdateScalingParameters' :: UpdateScalingParameters -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
domainName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ScalingParameters
scalingParameters
instance Data.ToHeaders UpdateScalingParameters where
  toHeaders :: UpdateScalingParameters -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
instance Data.ToPath UpdateScalingParameters where
  toPath :: UpdateScalingParameters -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery UpdateScalingParameters where
  toQuery :: UpdateScalingParameters -> QueryString
toQuery UpdateScalingParameters' {Text
ScalingParameters
scalingParameters :: ScalingParameters
domainName :: Text
$sel:scalingParameters:UpdateScalingParameters' :: UpdateScalingParameters -> ScalingParameters
$sel:domainName:UpdateScalingParameters' :: UpdateScalingParameters -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"UpdateScalingParameters" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2013-01-01" :: Prelude.ByteString),
        ByteString
"DomainName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
domainName,
        ByteString
"ScalingParameters" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ScalingParameters
scalingParameters
      ]
data UpdateScalingParametersResponse = UpdateScalingParametersResponse'
  { 
    UpdateScalingParametersResponse -> Int
httpStatus :: Prelude.Int,
    UpdateScalingParametersResponse -> ScalingParametersStatus
scalingParameters :: ScalingParametersStatus
  }
  deriving (UpdateScalingParametersResponse
-> UpdateScalingParametersResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateScalingParametersResponse
-> UpdateScalingParametersResponse -> Bool
$c/= :: UpdateScalingParametersResponse
-> UpdateScalingParametersResponse -> Bool
== :: UpdateScalingParametersResponse
-> UpdateScalingParametersResponse -> Bool
$c== :: UpdateScalingParametersResponse
-> UpdateScalingParametersResponse -> Bool
Prelude.Eq, ReadPrec [UpdateScalingParametersResponse]
ReadPrec UpdateScalingParametersResponse
Int -> ReadS UpdateScalingParametersResponse
ReadS [UpdateScalingParametersResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateScalingParametersResponse]
$creadListPrec :: ReadPrec [UpdateScalingParametersResponse]
readPrec :: ReadPrec UpdateScalingParametersResponse
$creadPrec :: ReadPrec UpdateScalingParametersResponse
readList :: ReadS [UpdateScalingParametersResponse]
$creadList :: ReadS [UpdateScalingParametersResponse]
readsPrec :: Int -> ReadS UpdateScalingParametersResponse
$creadsPrec :: Int -> ReadS UpdateScalingParametersResponse
Prelude.Read, Int -> UpdateScalingParametersResponse -> ShowS
[UpdateScalingParametersResponse] -> ShowS
UpdateScalingParametersResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateScalingParametersResponse] -> ShowS
$cshowList :: [UpdateScalingParametersResponse] -> ShowS
show :: UpdateScalingParametersResponse -> String
$cshow :: UpdateScalingParametersResponse -> String
showsPrec :: Int -> UpdateScalingParametersResponse -> ShowS
$cshowsPrec :: Int -> UpdateScalingParametersResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateScalingParametersResponse x
-> UpdateScalingParametersResponse
forall x.
UpdateScalingParametersResponse
-> Rep UpdateScalingParametersResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateScalingParametersResponse x
-> UpdateScalingParametersResponse
$cfrom :: forall x.
UpdateScalingParametersResponse
-> Rep UpdateScalingParametersResponse x
Prelude.Generic)
newUpdateScalingParametersResponse ::
  
  Prelude.Int ->
  
  ScalingParametersStatus ->
  UpdateScalingParametersResponse
newUpdateScalingParametersResponse :: Int -> ScalingParametersStatus -> UpdateScalingParametersResponse
newUpdateScalingParametersResponse
  Int
pHttpStatus_
  ScalingParametersStatus
pScalingParameters_ =
    UpdateScalingParametersResponse'
      { $sel:httpStatus:UpdateScalingParametersResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:scalingParameters:UpdateScalingParametersResponse' :: ScalingParametersStatus
scalingParameters = ScalingParametersStatus
pScalingParameters_
      }
updateScalingParametersResponse_httpStatus :: Lens.Lens' UpdateScalingParametersResponse Prelude.Int
updateScalingParametersResponse_httpStatus :: Lens' UpdateScalingParametersResponse Int
updateScalingParametersResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateScalingParametersResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateScalingParametersResponse' :: UpdateScalingParametersResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdateScalingParametersResponse
s@UpdateScalingParametersResponse' {} Int
a -> UpdateScalingParametersResponse
s {$sel:httpStatus:UpdateScalingParametersResponse' :: Int
httpStatus = Int
a} :: UpdateScalingParametersResponse)
updateScalingParametersResponse_scalingParameters :: Lens.Lens' UpdateScalingParametersResponse ScalingParametersStatus
updateScalingParametersResponse_scalingParameters :: Lens' UpdateScalingParametersResponse ScalingParametersStatus
updateScalingParametersResponse_scalingParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateScalingParametersResponse' {ScalingParametersStatus
scalingParameters :: ScalingParametersStatus
$sel:scalingParameters:UpdateScalingParametersResponse' :: UpdateScalingParametersResponse -> ScalingParametersStatus
scalingParameters} -> ScalingParametersStatus
scalingParameters) (\s :: UpdateScalingParametersResponse
s@UpdateScalingParametersResponse' {} ScalingParametersStatus
a -> UpdateScalingParametersResponse
s {$sel:scalingParameters:UpdateScalingParametersResponse' :: ScalingParametersStatus
scalingParameters = ScalingParametersStatus
a} :: UpdateScalingParametersResponse)
instance
  Prelude.NFData
    UpdateScalingParametersResponse
  where
  rnf :: UpdateScalingParametersResponse -> ()
rnf UpdateScalingParametersResponse' {Int
ScalingParametersStatus
scalingParameters :: ScalingParametersStatus
httpStatus :: Int
$sel:scalingParameters:UpdateScalingParametersResponse' :: UpdateScalingParametersResponse -> ScalingParametersStatus
$sel:httpStatus:UpdateScalingParametersResponse' :: UpdateScalingParametersResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ScalingParametersStatus
scalingParameters