{-# 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.MediaLive.UpdateReservation
(
UpdateReservation' (..),
newUpdateReservation',
updateReservation'_name,
updateReservation'_renewalSettings,
updateReservation'_reservationId,
UpdateReservationResponse (..),
newUpdateReservationResponse,
updateReservationResponse_reservation,
updateReservationResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.MediaLive.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data UpdateReservation' = UpdateReservation''
{
UpdateReservation' -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
UpdateReservation' -> Maybe RenewalSettings
renewalSettings :: Prelude.Maybe RenewalSettings,
UpdateReservation' -> Text
reservationId :: Prelude.Text
}
deriving (UpdateReservation' -> UpdateReservation' -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateReservation' -> UpdateReservation' -> Bool
$c/= :: UpdateReservation' -> UpdateReservation' -> Bool
== :: UpdateReservation' -> UpdateReservation' -> Bool
$c== :: UpdateReservation' -> UpdateReservation' -> Bool
Prelude.Eq, ReadPrec [UpdateReservation']
ReadPrec UpdateReservation'
Int -> ReadS UpdateReservation'
ReadS [UpdateReservation']
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateReservation']
$creadListPrec :: ReadPrec [UpdateReservation']
readPrec :: ReadPrec UpdateReservation'
$creadPrec :: ReadPrec UpdateReservation'
readList :: ReadS [UpdateReservation']
$creadList :: ReadS [UpdateReservation']
readsPrec :: Int -> ReadS UpdateReservation'
$creadsPrec :: Int -> ReadS UpdateReservation'
Prelude.Read, Int -> UpdateReservation' -> ShowS
[UpdateReservation'] -> ShowS
UpdateReservation' -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateReservation'] -> ShowS
$cshowList :: [UpdateReservation'] -> ShowS
show :: UpdateReservation' -> String
$cshow :: UpdateReservation' -> String
showsPrec :: Int -> UpdateReservation' -> ShowS
$cshowsPrec :: Int -> UpdateReservation' -> ShowS
Prelude.Show, forall x. Rep UpdateReservation' x -> UpdateReservation'
forall x. UpdateReservation' -> Rep UpdateReservation' x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateReservation' x -> UpdateReservation'
$cfrom :: forall x. UpdateReservation' -> Rep UpdateReservation' x
Prelude.Generic)
newUpdateReservation' ::
Prelude.Text ->
UpdateReservation'
newUpdateReservation' :: Text -> UpdateReservation'
newUpdateReservation' Text
pReservationId_ =
UpdateReservation''
{ $sel:name:UpdateReservation'' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
$sel:renewalSettings:UpdateReservation'' :: Maybe RenewalSettings
renewalSettings = forall a. Maybe a
Prelude.Nothing,
$sel:reservationId:UpdateReservation'' :: Text
reservationId = Text
pReservationId_
}
updateReservation'_name :: Lens.Lens' UpdateReservation' (Prelude.Maybe Prelude.Text)
updateReservation'_name :: Lens' UpdateReservation' (Maybe Text)
updateReservation'_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateReservation'' {Maybe Text
name :: Maybe Text
$sel:name:UpdateReservation'' :: UpdateReservation' -> Maybe Text
name} -> Maybe Text
name) (\s :: UpdateReservation'
s@UpdateReservation'' {} Maybe Text
a -> UpdateReservation'
s {$sel:name:UpdateReservation'' :: Maybe Text
name = Maybe Text
a} :: UpdateReservation')
updateReservation'_renewalSettings :: Lens.Lens' UpdateReservation' (Prelude.Maybe RenewalSettings)
updateReservation'_renewalSettings :: Lens' UpdateReservation' (Maybe RenewalSettings)
updateReservation'_renewalSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateReservation'' {Maybe RenewalSettings
renewalSettings :: Maybe RenewalSettings
$sel:renewalSettings:UpdateReservation'' :: UpdateReservation' -> Maybe RenewalSettings
renewalSettings} -> Maybe RenewalSettings
renewalSettings) (\s :: UpdateReservation'
s@UpdateReservation'' {} Maybe RenewalSettings
a -> UpdateReservation'
s {$sel:renewalSettings:UpdateReservation'' :: Maybe RenewalSettings
renewalSettings = Maybe RenewalSettings
a} :: UpdateReservation')
updateReservation'_reservationId :: Lens.Lens' UpdateReservation' Prelude.Text
updateReservation'_reservationId :: Lens' UpdateReservation' Text
updateReservation'_reservationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateReservation'' {Text
reservationId :: Text
$sel:reservationId:UpdateReservation'' :: UpdateReservation' -> Text
reservationId} -> Text
reservationId) (\s :: UpdateReservation'
s@UpdateReservation'' {} Text
a -> UpdateReservation'
s {$sel:reservationId:UpdateReservation'' :: Text
reservationId = Text
a} :: UpdateReservation')
instance Core.AWSRequest UpdateReservation' where
type
AWSResponse UpdateReservation' =
UpdateReservationResponse
request :: (Service -> Service)
-> UpdateReservation' -> Request UpdateReservation'
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 UpdateReservation'
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse UpdateReservation')))
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 Reservation -> Int -> UpdateReservationResponse
UpdateReservationResponse'
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
"reservation")
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 UpdateReservation' where
hashWithSalt :: Int -> UpdateReservation' -> Int
hashWithSalt Int
_salt UpdateReservation'' {Maybe Text
Maybe RenewalSettings
Text
reservationId :: Text
renewalSettings :: Maybe RenewalSettings
name :: Maybe Text
$sel:reservationId:UpdateReservation'' :: UpdateReservation' -> Text
$sel:renewalSettings:UpdateReservation'' :: UpdateReservation' -> Maybe RenewalSettings
$sel:name:UpdateReservation'' :: UpdateReservation' -> Maybe Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RenewalSettings
renewalSettings
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
reservationId
instance Prelude.NFData UpdateReservation' where
rnf :: UpdateReservation' -> ()
rnf UpdateReservation'' {Maybe Text
Maybe RenewalSettings
Text
reservationId :: Text
renewalSettings :: Maybe RenewalSettings
name :: Maybe Text
$sel:reservationId:UpdateReservation'' :: UpdateReservation' -> Text
$sel:renewalSettings:UpdateReservation'' :: UpdateReservation' -> Maybe RenewalSettings
$sel:name:UpdateReservation'' :: UpdateReservation' -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RenewalSettings
renewalSettings
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
reservationId
instance Data.ToHeaders UpdateReservation' where
toHeaders :: UpdateReservation' -> 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 UpdateReservation' where
toJSON :: UpdateReservation' -> Value
toJSON UpdateReservation'' {Maybe Text
Maybe RenewalSettings
Text
reservationId :: Text
renewalSettings :: Maybe RenewalSettings
name :: Maybe Text
$sel:reservationId:UpdateReservation'' :: UpdateReservation' -> Text
$sel:renewalSettings:UpdateReservation'' :: UpdateReservation' -> Maybe RenewalSettings
$sel:name:UpdateReservation'' :: UpdateReservation' -> Maybe Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
name,
(Key
"renewalSettings" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe RenewalSettings
renewalSettings
]
)
instance Data.ToPath UpdateReservation' where
toPath :: UpdateReservation' -> ByteString
toPath UpdateReservation'' {Maybe Text
Maybe RenewalSettings
Text
reservationId :: Text
renewalSettings :: Maybe RenewalSettings
name :: Maybe Text
$sel:reservationId:UpdateReservation'' :: UpdateReservation' -> Text
$sel:renewalSettings:UpdateReservation'' :: UpdateReservation' -> Maybe RenewalSettings
$sel:name:UpdateReservation'' :: UpdateReservation' -> Maybe Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ByteString
"/prod/reservations/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
reservationId]
instance Data.ToQuery UpdateReservation' where
toQuery :: UpdateReservation' -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data UpdateReservationResponse = UpdateReservationResponse'
{ UpdateReservationResponse -> Maybe Reservation
reservation :: Prelude.Maybe Reservation,
UpdateReservationResponse -> Int
httpStatus :: Prelude.Int
}
deriving (UpdateReservationResponse -> UpdateReservationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateReservationResponse -> UpdateReservationResponse -> Bool
$c/= :: UpdateReservationResponse -> UpdateReservationResponse -> Bool
== :: UpdateReservationResponse -> UpdateReservationResponse -> Bool
$c== :: UpdateReservationResponse -> UpdateReservationResponse -> Bool
Prelude.Eq, ReadPrec [UpdateReservationResponse]
ReadPrec UpdateReservationResponse
Int -> ReadS UpdateReservationResponse
ReadS [UpdateReservationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateReservationResponse]
$creadListPrec :: ReadPrec [UpdateReservationResponse]
readPrec :: ReadPrec UpdateReservationResponse
$creadPrec :: ReadPrec UpdateReservationResponse
readList :: ReadS [UpdateReservationResponse]
$creadList :: ReadS [UpdateReservationResponse]
readsPrec :: Int -> ReadS UpdateReservationResponse
$creadsPrec :: Int -> ReadS UpdateReservationResponse
Prelude.Read, Int -> UpdateReservationResponse -> ShowS
[UpdateReservationResponse] -> ShowS
UpdateReservationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateReservationResponse] -> ShowS
$cshowList :: [UpdateReservationResponse] -> ShowS
show :: UpdateReservationResponse -> String
$cshow :: UpdateReservationResponse -> String
showsPrec :: Int -> UpdateReservationResponse -> ShowS
$cshowsPrec :: Int -> UpdateReservationResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateReservationResponse x -> UpdateReservationResponse
forall x.
UpdateReservationResponse -> Rep UpdateReservationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateReservationResponse x -> UpdateReservationResponse
$cfrom :: forall x.
UpdateReservationResponse -> Rep UpdateReservationResponse x
Prelude.Generic)
newUpdateReservationResponse ::
Prelude.Int ->
UpdateReservationResponse
newUpdateReservationResponse :: Int -> UpdateReservationResponse
newUpdateReservationResponse Int
pHttpStatus_ =
UpdateReservationResponse'
{ $sel:reservation:UpdateReservationResponse' :: Maybe Reservation
reservation =
forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:UpdateReservationResponse' :: Int
httpStatus = Int
pHttpStatus_
}
updateReservationResponse_reservation :: Lens.Lens' UpdateReservationResponse (Prelude.Maybe Reservation)
updateReservationResponse_reservation :: Lens' UpdateReservationResponse (Maybe Reservation)
updateReservationResponse_reservation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateReservationResponse' {Maybe Reservation
reservation :: Maybe Reservation
$sel:reservation:UpdateReservationResponse' :: UpdateReservationResponse -> Maybe Reservation
reservation} -> Maybe Reservation
reservation) (\s :: UpdateReservationResponse
s@UpdateReservationResponse' {} Maybe Reservation
a -> UpdateReservationResponse
s {$sel:reservation:UpdateReservationResponse' :: Maybe Reservation
reservation = Maybe Reservation
a} :: UpdateReservationResponse)
updateReservationResponse_httpStatus :: Lens.Lens' UpdateReservationResponse Prelude.Int
updateReservationResponse_httpStatus :: Lens' UpdateReservationResponse Int
updateReservationResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateReservationResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateReservationResponse' :: UpdateReservationResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdateReservationResponse
s@UpdateReservationResponse' {} Int
a -> UpdateReservationResponse
s {$sel:httpStatus:UpdateReservationResponse' :: Int
httpStatus = Int
a} :: UpdateReservationResponse)
instance Prelude.NFData UpdateReservationResponse where
rnf :: UpdateReservationResponse -> ()
rnf UpdateReservationResponse' {Int
Maybe Reservation
httpStatus :: Int
reservation :: Maybe Reservation
$sel:httpStatus:UpdateReservationResponse' :: UpdateReservationResponse -> Int
$sel:reservation:UpdateReservationResponse' :: UpdateReservationResponse -> Maybe Reservation
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Reservation
reservation
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus