{-# 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.Pinpoint.UpdateRecommenderConfiguration
(
UpdateRecommenderConfiguration' (..),
newUpdateRecommenderConfiguration',
updateRecommenderConfiguration'_recommenderId,
updateRecommenderConfiguration'_updateRecommenderConfiguration,
UpdateRecommenderConfigurationResponse (..),
newUpdateRecommenderConfigurationResponse,
updateRecommenderConfigurationResponse_httpStatus,
updateRecommenderConfigurationResponse_recommenderConfigurationResponse,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Pinpoint.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data UpdateRecommenderConfiguration' = UpdateRecommenderConfiguration''
{
UpdateRecommenderConfiguration' -> Text
recommenderId :: Prelude.Text,
UpdateRecommenderConfiguration' -> UpdateRecommenderConfiguration
updateRecommenderConfiguration :: UpdateRecommenderConfiguration
}
deriving (UpdateRecommenderConfiguration'
-> UpdateRecommenderConfiguration' -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateRecommenderConfiguration'
-> UpdateRecommenderConfiguration' -> Bool
$c/= :: UpdateRecommenderConfiguration'
-> UpdateRecommenderConfiguration' -> Bool
== :: UpdateRecommenderConfiguration'
-> UpdateRecommenderConfiguration' -> Bool
$c== :: UpdateRecommenderConfiguration'
-> UpdateRecommenderConfiguration' -> Bool
Prelude.Eq, ReadPrec [UpdateRecommenderConfiguration']
ReadPrec UpdateRecommenderConfiguration'
Int -> ReadS UpdateRecommenderConfiguration'
ReadS [UpdateRecommenderConfiguration']
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateRecommenderConfiguration']
$creadListPrec :: ReadPrec [UpdateRecommenderConfiguration']
readPrec :: ReadPrec UpdateRecommenderConfiguration'
$creadPrec :: ReadPrec UpdateRecommenderConfiguration'
readList :: ReadS [UpdateRecommenderConfiguration']
$creadList :: ReadS [UpdateRecommenderConfiguration']
readsPrec :: Int -> ReadS UpdateRecommenderConfiguration'
$creadsPrec :: Int -> ReadS UpdateRecommenderConfiguration'
Prelude.Read, Int -> UpdateRecommenderConfiguration' -> ShowS
[UpdateRecommenderConfiguration'] -> ShowS
UpdateRecommenderConfiguration' -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateRecommenderConfiguration'] -> ShowS
$cshowList :: [UpdateRecommenderConfiguration'] -> ShowS
show :: UpdateRecommenderConfiguration' -> String
$cshow :: UpdateRecommenderConfiguration' -> String
showsPrec :: Int -> UpdateRecommenderConfiguration' -> ShowS
$cshowsPrec :: Int -> UpdateRecommenderConfiguration' -> ShowS
Prelude.Show, forall x.
Rep UpdateRecommenderConfiguration' x
-> UpdateRecommenderConfiguration'
forall x.
UpdateRecommenderConfiguration'
-> Rep UpdateRecommenderConfiguration' x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateRecommenderConfiguration' x
-> UpdateRecommenderConfiguration'
$cfrom :: forall x.
UpdateRecommenderConfiguration'
-> Rep UpdateRecommenderConfiguration' x
Prelude.Generic)
newUpdateRecommenderConfiguration' ::
Prelude.Text ->
UpdateRecommenderConfiguration ->
UpdateRecommenderConfiguration'
newUpdateRecommenderConfiguration' :: Text
-> UpdateRecommenderConfiguration
-> UpdateRecommenderConfiguration'
newUpdateRecommenderConfiguration'
Text
pRecommenderId_
UpdateRecommenderConfiguration
pUpdateRecommenderConfiguration_ =
UpdateRecommenderConfiguration''
{ $sel:recommenderId:UpdateRecommenderConfiguration'' :: Text
recommenderId =
Text
pRecommenderId_,
$sel:updateRecommenderConfiguration:UpdateRecommenderConfiguration'' :: UpdateRecommenderConfiguration
updateRecommenderConfiguration =
UpdateRecommenderConfiguration
pUpdateRecommenderConfiguration_
}
updateRecommenderConfiguration'_recommenderId :: Lens.Lens' UpdateRecommenderConfiguration' Prelude.Text
updateRecommenderConfiguration'_recommenderId :: Lens' UpdateRecommenderConfiguration' Text
updateRecommenderConfiguration'_recommenderId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRecommenderConfiguration'' {Text
recommenderId :: Text
$sel:recommenderId:UpdateRecommenderConfiguration'' :: UpdateRecommenderConfiguration' -> Text
recommenderId} -> Text
recommenderId) (\s :: UpdateRecommenderConfiguration'
s@UpdateRecommenderConfiguration'' {} Text
a -> UpdateRecommenderConfiguration'
s {$sel:recommenderId:UpdateRecommenderConfiguration'' :: Text
recommenderId = Text
a} :: UpdateRecommenderConfiguration')
updateRecommenderConfiguration'_updateRecommenderConfiguration :: Lens.Lens' UpdateRecommenderConfiguration' UpdateRecommenderConfiguration
updateRecommenderConfiguration'_updateRecommenderConfiguration :: Lens'
UpdateRecommenderConfiguration' UpdateRecommenderConfiguration
updateRecommenderConfiguration'_updateRecommenderConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRecommenderConfiguration'' {UpdateRecommenderConfiguration
updateRecommenderConfiguration :: UpdateRecommenderConfiguration
$sel:updateRecommenderConfiguration:UpdateRecommenderConfiguration'' :: UpdateRecommenderConfiguration' -> UpdateRecommenderConfiguration
updateRecommenderConfiguration} -> UpdateRecommenderConfiguration
updateRecommenderConfiguration) (\s :: UpdateRecommenderConfiguration'
s@UpdateRecommenderConfiguration'' {} UpdateRecommenderConfiguration
a -> UpdateRecommenderConfiguration'
s {$sel:updateRecommenderConfiguration:UpdateRecommenderConfiguration'' :: UpdateRecommenderConfiguration
updateRecommenderConfiguration = UpdateRecommenderConfiguration
a} :: UpdateRecommenderConfiguration')
instance
Core.AWSRequest
UpdateRecommenderConfiguration'
where
type
AWSResponse UpdateRecommenderConfiguration' =
UpdateRecommenderConfigurationResponse
request :: (Service -> Service)
-> UpdateRecommenderConfiguration'
-> Request UpdateRecommenderConfiguration'
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 UpdateRecommenderConfiguration'
-> ClientResponse ClientBody
-> m (Either
Error
(ClientResponse (AWSResponse UpdateRecommenderConfiguration')))
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 ->
Int
-> RecommenderConfigurationResponse
-> UpdateRecommenderConfigurationResponse
UpdateRecommenderConfigurationResponse'
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.<*> (forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)
)
instance
Prelude.Hashable
UpdateRecommenderConfiguration'
where
hashWithSalt :: Int -> UpdateRecommenderConfiguration' -> Int
hashWithSalt
Int
_salt
UpdateRecommenderConfiguration'' {Text
UpdateRecommenderConfiguration
updateRecommenderConfiguration :: UpdateRecommenderConfiguration
recommenderId :: Text
$sel:updateRecommenderConfiguration:UpdateRecommenderConfiguration'' :: UpdateRecommenderConfiguration' -> UpdateRecommenderConfiguration
$sel:recommenderId:UpdateRecommenderConfiguration'' :: UpdateRecommenderConfiguration' -> Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
recommenderId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` UpdateRecommenderConfiguration
updateRecommenderConfiguration
instance
Prelude.NFData
UpdateRecommenderConfiguration'
where
rnf :: UpdateRecommenderConfiguration' -> ()
rnf UpdateRecommenderConfiguration'' {Text
UpdateRecommenderConfiguration
updateRecommenderConfiguration :: UpdateRecommenderConfiguration
recommenderId :: Text
$sel:updateRecommenderConfiguration:UpdateRecommenderConfiguration'' :: UpdateRecommenderConfiguration' -> UpdateRecommenderConfiguration
$sel:recommenderId:UpdateRecommenderConfiguration'' :: UpdateRecommenderConfiguration' -> Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Text
recommenderId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf UpdateRecommenderConfiguration
updateRecommenderConfiguration
instance
Data.ToHeaders
UpdateRecommenderConfiguration'
where
toHeaders :: UpdateRecommenderConfiguration' -> 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 UpdateRecommenderConfiguration' where
toJSON :: UpdateRecommenderConfiguration' -> Value
toJSON UpdateRecommenderConfiguration'' {Text
UpdateRecommenderConfiguration
updateRecommenderConfiguration :: UpdateRecommenderConfiguration
recommenderId :: Text
$sel:updateRecommenderConfiguration:UpdateRecommenderConfiguration'' :: UpdateRecommenderConfiguration' -> UpdateRecommenderConfiguration
$sel:recommenderId:UpdateRecommenderConfiguration'' :: UpdateRecommenderConfiguration' -> Text
..} =
forall a. ToJSON a => a -> Value
Data.toJSON UpdateRecommenderConfiguration
updateRecommenderConfiguration
instance Data.ToPath UpdateRecommenderConfiguration' where
toPath :: UpdateRecommenderConfiguration' -> ByteString
toPath UpdateRecommenderConfiguration'' {Text
UpdateRecommenderConfiguration
updateRecommenderConfiguration :: UpdateRecommenderConfiguration
recommenderId :: Text
$sel:updateRecommenderConfiguration:UpdateRecommenderConfiguration'' :: UpdateRecommenderConfiguration' -> UpdateRecommenderConfiguration
$sel:recommenderId:UpdateRecommenderConfiguration'' :: UpdateRecommenderConfiguration' -> Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ByteString
"/v1/recommenders/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
recommenderId]
instance Data.ToQuery UpdateRecommenderConfiguration' where
toQuery :: UpdateRecommenderConfiguration' -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data UpdateRecommenderConfigurationResponse = UpdateRecommenderConfigurationResponse'
{
UpdateRecommenderConfigurationResponse -> Int
httpStatus :: Prelude.Int,
UpdateRecommenderConfigurationResponse
-> RecommenderConfigurationResponse
recommenderConfigurationResponse :: RecommenderConfigurationResponse
}
deriving (UpdateRecommenderConfigurationResponse
-> UpdateRecommenderConfigurationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateRecommenderConfigurationResponse
-> UpdateRecommenderConfigurationResponse -> Bool
$c/= :: UpdateRecommenderConfigurationResponse
-> UpdateRecommenderConfigurationResponse -> Bool
== :: UpdateRecommenderConfigurationResponse
-> UpdateRecommenderConfigurationResponse -> Bool
$c== :: UpdateRecommenderConfigurationResponse
-> UpdateRecommenderConfigurationResponse -> Bool
Prelude.Eq, ReadPrec [UpdateRecommenderConfigurationResponse]
ReadPrec UpdateRecommenderConfigurationResponse
Int -> ReadS UpdateRecommenderConfigurationResponse
ReadS [UpdateRecommenderConfigurationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateRecommenderConfigurationResponse]
$creadListPrec :: ReadPrec [UpdateRecommenderConfigurationResponse]
readPrec :: ReadPrec UpdateRecommenderConfigurationResponse
$creadPrec :: ReadPrec UpdateRecommenderConfigurationResponse
readList :: ReadS [UpdateRecommenderConfigurationResponse]
$creadList :: ReadS [UpdateRecommenderConfigurationResponse]
readsPrec :: Int -> ReadS UpdateRecommenderConfigurationResponse
$creadsPrec :: Int -> ReadS UpdateRecommenderConfigurationResponse
Prelude.Read, Int -> UpdateRecommenderConfigurationResponse -> ShowS
[UpdateRecommenderConfigurationResponse] -> ShowS
UpdateRecommenderConfigurationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateRecommenderConfigurationResponse] -> ShowS
$cshowList :: [UpdateRecommenderConfigurationResponse] -> ShowS
show :: UpdateRecommenderConfigurationResponse -> String
$cshow :: UpdateRecommenderConfigurationResponse -> String
showsPrec :: Int -> UpdateRecommenderConfigurationResponse -> ShowS
$cshowsPrec :: Int -> UpdateRecommenderConfigurationResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateRecommenderConfigurationResponse x
-> UpdateRecommenderConfigurationResponse
forall x.
UpdateRecommenderConfigurationResponse
-> Rep UpdateRecommenderConfigurationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateRecommenderConfigurationResponse x
-> UpdateRecommenderConfigurationResponse
$cfrom :: forall x.
UpdateRecommenderConfigurationResponse
-> Rep UpdateRecommenderConfigurationResponse x
Prelude.Generic)
newUpdateRecommenderConfigurationResponse ::
Prelude.Int ->
RecommenderConfigurationResponse ->
UpdateRecommenderConfigurationResponse
newUpdateRecommenderConfigurationResponse :: Int
-> RecommenderConfigurationResponse
-> UpdateRecommenderConfigurationResponse
newUpdateRecommenderConfigurationResponse
Int
pHttpStatus_
RecommenderConfigurationResponse
pRecommenderConfigurationResponse_ =
UpdateRecommenderConfigurationResponse'
{ $sel:httpStatus:UpdateRecommenderConfigurationResponse' :: Int
httpStatus =
Int
pHttpStatus_,
$sel:recommenderConfigurationResponse:UpdateRecommenderConfigurationResponse' :: RecommenderConfigurationResponse
recommenderConfigurationResponse =
RecommenderConfigurationResponse
pRecommenderConfigurationResponse_
}
updateRecommenderConfigurationResponse_httpStatus :: Lens.Lens' UpdateRecommenderConfigurationResponse Prelude.Int
updateRecommenderConfigurationResponse_httpStatus :: Lens' UpdateRecommenderConfigurationResponse Int
updateRecommenderConfigurationResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRecommenderConfigurationResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateRecommenderConfigurationResponse' :: UpdateRecommenderConfigurationResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdateRecommenderConfigurationResponse
s@UpdateRecommenderConfigurationResponse' {} Int
a -> UpdateRecommenderConfigurationResponse
s {$sel:httpStatus:UpdateRecommenderConfigurationResponse' :: Int
httpStatus = Int
a} :: UpdateRecommenderConfigurationResponse)
updateRecommenderConfigurationResponse_recommenderConfigurationResponse :: Lens.Lens' UpdateRecommenderConfigurationResponse RecommenderConfigurationResponse
updateRecommenderConfigurationResponse_recommenderConfigurationResponse :: Lens'
UpdateRecommenderConfigurationResponse
RecommenderConfigurationResponse
updateRecommenderConfigurationResponse_recommenderConfigurationResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRecommenderConfigurationResponse' {RecommenderConfigurationResponse
recommenderConfigurationResponse :: RecommenderConfigurationResponse
$sel:recommenderConfigurationResponse:UpdateRecommenderConfigurationResponse' :: UpdateRecommenderConfigurationResponse
-> RecommenderConfigurationResponse
recommenderConfigurationResponse} -> RecommenderConfigurationResponse
recommenderConfigurationResponse) (\s :: UpdateRecommenderConfigurationResponse
s@UpdateRecommenderConfigurationResponse' {} RecommenderConfigurationResponse
a -> UpdateRecommenderConfigurationResponse
s {$sel:recommenderConfigurationResponse:UpdateRecommenderConfigurationResponse' :: RecommenderConfigurationResponse
recommenderConfigurationResponse = RecommenderConfigurationResponse
a} :: UpdateRecommenderConfigurationResponse)
instance
Prelude.NFData
UpdateRecommenderConfigurationResponse
where
rnf :: UpdateRecommenderConfigurationResponse -> ()
rnf UpdateRecommenderConfigurationResponse' {Int
RecommenderConfigurationResponse
recommenderConfigurationResponse :: RecommenderConfigurationResponse
httpStatus :: Int
$sel:recommenderConfigurationResponse:UpdateRecommenderConfigurationResponse' :: UpdateRecommenderConfigurationResponse
-> RecommenderConfigurationResponse
$sel:httpStatus:UpdateRecommenderConfigurationResponse' :: UpdateRecommenderConfigurationResponse -> 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 RecommenderConfigurationResponse
recommenderConfigurationResponse