{-# 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.Route53AutoNaming.UpdateService
(
UpdateService (..),
newUpdateService,
updateService_id,
updateService_service,
UpdateServiceResponse (..),
newUpdateServiceResponse,
updateServiceResponse_operationId,
updateServiceResponse_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.Route53AutoNaming.Types
data UpdateService = UpdateService'
{
UpdateService -> Text
id :: Prelude.Text,
UpdateService -> ServiceChange
service :: ServiceChange
}
deriving (UpdateService -> UpdateService -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateService -> UpdateService -> Bool
$c/= :: UpdateService -> UpdateService -> Bool
== :: UpdateService -> UpdateService -> Bool
$c== :: UpdateService -> UpdateService -> Bool
Prelude.Eq, ReadPrec [UpdateService]
ReadPrec UpdateService
Int -> ReadS UpdateService
ReadS [UpdateService]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateService]
$creadListPrec :: ReadPrec [UpdateService]
readPrec :: ReadPrec UpdateService
$creadPrec :: ReadPrec UpdateService
readList :: ReadS [UpdateService]
$creadList :: ReadS [UpdateService]
readsPrec :: Int -> ReadS UpdateService
$creadsPrec :: Int -> ReadS UpdateService
Prelude.Read, Int -> UpdateService -> ShowS
[UpdateService] -> ShowS
UpdateService -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateService] -> ShowS
$cshowList :: [UpdateService] -> ShowS
show :: UpdateService -> String
$cshow :: UpdateService -> String
showsPrec :: Int -> UpdateService -> ShowS
$cshowsPrec :: Int -> UpdateService -> ShowS
Prelude.Show, forall x. Rep UpdateService x -> UpdateService
forall x. UpdateService -> Rep UpdateService x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateService x -> UpdateService
$cfrom :: forall x. UpdateService -> Rep UpdateService x
Prelude.Generic)
newUpdateService ::
Prelude.Text ->
ServiceChange ->
UpdateService
newUpdateService :: Text -> ServiceChange -> UpdateService
newUpdateService Text
pId_ ServiceChange
pService_ =
UpdateService' {$sel:id:UpdateService' :: Text
id = Text
pId_, $sel:service:UpdateService' :: ServiceChange
service = ServiceChange
pService_}
updateService_id :: Lens.Lens' UpdateService Prelude.Text
updateService_id :: Lens' UpdateService Text
updateService_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateService' {Text
id :: Text
$sel:id:UpdateService' :: UpdateService -> Text
id} -> Text
id) (\s :: UpdateService
s@UpdateService' {} Text
a -> UpdateService
s {$sel:id:UpdateService' :: Text
id = Text
a} :: UpdateService)
updateService_service :: Lens.Lens' UpdateService ServiceChange
updateService_service :: Lens' UpdateService ServiceChange
updateService_service = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateService' {ServiceChange
service :: ServiceChange
$sel:service:UpdateService' :: UpdateService -> ServiceChange
service} -> ServiceChange
service) (\s :: UpdateService
s@UpdateService' {} ServiceChange
a -> UpdateService
s {$sel:service:UpdateService' :: ServiceChange
service = ServiceChange
a} :: UpdateService)
instance Core.AWSRequest UpdateService where
type
AWSResponse UpdateService =
UpdateServiceResponse
request :: (Service -> Service) -> UpdateService -> Request UpdateService
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 UpdateService
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateService)))
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 Text -> Int -> UpdateServiceResponse
UpdateServiceResponse'
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
"OperationId")
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 UpdateService where
hashWithSalt :: Int -> UpdateService -> Int
hashWithSalt Int
_salt UpdateService' {Text
ServiceChange
service :: ServiceChange
id :: Text
$sel:service:UpdateService' :: UpdateService -> ServiceChange
$sel:id:UpdateService' :: UpdateService -> Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ServiceChange
service
instance Prelude.NFData UpdateService where
rnf :: UpdateService -> ()
rnf UpdateService' {Text
ServiceChange
service :: ServiceChange
id :: Text
$sel:service:UpdateService' :: UpdateService -> ServiceChange
$sel:id:UpdateService' :: UpdateService -> Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Text
id seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ServiceChange
service
instance Data.ToHeaders UpdateService where
toHeaders :: UpdateService -> 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
"Route53AutoNaming_v20170314.UpdateService" ::
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 UpdateService where
toJSON :: UpdateService -> Value
toJSON UpdateService' {Text
ServiceChange
service :: ServiceChange
id :: Text
$sel:service:UpdateService' :: UpdateService -> ServiceChange
$sel:id:UpdateService' :: UpdateService -> Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ forall a. a -> Maybe a
Prelude.Just (Key
"Id" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
id),
forall a. a -> Maybe a
Prelude.Just (Key
"Service" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ServiceChange
service)
]
)
instance Data.ToPath UpdateService where
toPath :: UpdateService -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery UpdateService where
toQuery :: UpdateService -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data UpdateServiceResponse = UpdateServiceResponse'
{
UpdateServiceResponse -> Maybe Text
operationId :: Prelude.Maybe Prelude.Text,
UpdateServiceResponse -> Int
httpStatus :: Prelude.Int
}
deriving (UpdateServiceResponse -> UpdateServiceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateServiceResponse -> UpdateServiceResponse -> Bool
$c/= :: UpdateServiceResponse -> UpdateServiceResponse -> Bool
== :: UpdateServiceResponse -> UpdateServiceResponse -> Bool
$c== :: UpdateServiceResponse -> UpdateServiceResponse -> Bool
Prelude.Eq, ReadPrec [UpdateServiceResponse]
ReadPrec UpdateServiceResponse
Int -> ReadS UpdateServiceResponse
ReadS [UpdateServiceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateServiceResponse]
$creadListPrec :: ReadPrec [UpdateServiceResponse]
readPrec :: ReadPrec UpdateServiceResponse
$creadPrec :: ReadPrec UpdateServiceResponse
readList :: ReadS [UpdateServiceResponse]
$creadList :: ReadS [UpdateServiceResponse]
readsPrec :: Int -> ReadS UpdateServiceResponse
$creadsPrec :: Int -> ReadS UpdateServiceResponse
Prelude.Read, Int -> UpdateServiceResponse -> ShowS
[UpdateServiceResponse] -> ShowS
UpdateServiceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateServiceResponse] -> ShowS
$cshowList :: [UpdateServiceResponse] -> ShowS
show :: UpdateServiceResponse -> String
$cshow :: UpdateServiceResponse -> String
showsPrec :: Int -> UpdateServiceResponse -> ShowS
$cshowsPrec :: Int -> UpdateServiceResponse -> ShowS
Prelude.Show, forall x. Rep UpdateServiceResponse x -> UpdateServiceResponse
forall x. UpdateServiceResponse -> Rep UpdateServiceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateServiceResponse x -> UpdateServiceResponse
$cfrom :: forall x. UpdateServiceResponse -> Rep UpdateServiceResponse x
Prelude.Generic)
newUpdateServiceResponse ::
Prelude.Int ->
UpdateServiceResponse
newUpdateServiceResponse :: Int -> UpdateServiceResponse
newUpdateServiceResponse Int
pHttpStatus_ =
UpdateServiceResponse'
{ $sel:operationId:UpdateServiceResponse' :: Maybe Text
operationId =
forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:UpdateServiceResponse' :: Int
httpStatus = Int
pHttpStatus_
}
updateServiceResponse_operationId :: Lens.Lens' UpdateServiceResponse (Prelude.Maybe Prelude.Text)
updateServiceResponse_operationId :: Lens' UpdateServiceResponse (Maybe Text)
updateServiceResponse_operationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateServiceResponse' {Maybe Text
operationId :: Maybe Text
$sel:operationId:UpdateServiceResponse' :: UpdateServiceResponse -> Maybe Text
operationId} -> Maybe Text
operationId) (\s :: UpdateServiceResponse
s@UpdateServiceResponse' {} Maybe Text
a -> UpdateServiceResponse
s {$sel:operationId:UpdateServiceResponse' :: Maybe Text
operationId = Maybe Text
a} :: UpdateServiceResponse)
updateServiceResponse_httpStatus :: Lens.Lens' UpdateServiceResponse Prelude.Int
updateServiceResponse_httpStatus :: Lens' UpdateServiceResponse Int
updateServiceResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateServiceResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateServiceResponse' :: UpdateServiceResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdateServiceResponse
s@UpdateServiceResponse' {} Int
a -> UpdateServiceResponse
s {$sel:httpStatus:UpdateServiceResponse' :: Int
httpStatus = Int
a} :: UpdateServiceResponse)
instance Prelude.NFData UpdateServiceResponse where
rnf :: UpdateServiceResponse -> ()
rnf UpdateServiceResponse' {Int
Maybe Text
httpStatus :: Int
operationId :: Maybe Text
$sel:httpStatus:UpdateServiceResponse' :: UpdateServiceResponse -> Int
$sel:operationId:UpdateServiceResponse' :: UpdateServiceResponse -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
operationId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus