{-# 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.CodePipeline.PutWebhook
(
PutWebhook (..),
newPutWebhook,
putWebhook_tags,
putWebhook_webhook,
PutWebhookResponse (..),
newPutWebhookResponse,
putWebhookResponse_webhook,
putWebhookResponse_httpStatus,
)
where
import Amazonka.CodePipeline.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 PutWebhook = PutWebhook'
{
PutWebhook -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
PutWebhook -> WebhookDefinition
webhook :: WebhookDefinition
}
deriving (PutWebhook -> PutWebhook -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutWebhook -> PutWebhook -> Bool
$c/= :: PutWebhook -> PutWebhook -> Bool
== :: PutWebhook -> PutWebhook -> Bool
$c== :: PutWebhook -> PutWebhook -> Bool
Prelude.Eq, ReadPrec [PutWebhook]
ReadPrec PutWebhook
Int -> ReadS PutWebhook
ReadS [PutWebhook]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutWebhook]
$creadListPrec :: ReadPrec [PutWebhook]
readPrec :: ReadPrec PutWebhook
$creadPrec :: ReadPrec PutWebhook
readList :: ReadS [PutWebhook]
$creadList :: ReadS [PutWebhook]
readsPrec :: Int -> ReadS PutWebhook
$creadsPrec :: Int -> ReadS PutWebhook
Prelude.Read, Int -> PutWebhook -> ShowS
[PutWebhook] -> ShowS
PutWebhook -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutWebhook] -> ShowS
$cshowList :: [PutWebhook] -> ShowS
show :: PutWebhook -> String
$cshow :: PutWebhook -> String
showsPrec :: Int -> PutWebhook -> ShowS
$cshowsPrec :: Int -> PutWebhook -> ShowS
Prelude.Show, forall x. Rep PutWebhook x -> PutWebhook
forall x. PutWebhook -> Rep PutWebhook x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutWebhook x -> PutWebhook
$cfrom :: forall x. PutWebhook -> Rep PutWebhook x
Prelude.Generic)
newPutWebhook ::
WebhookDefinition ->
PutWebhook
newPutWebhook :: WebhookDefinition -> PutWebhook
newPutWebhook WebhookDefinition
pWebhook_ =
PutWebhook'
{ $sel:tags:PutWebhook' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
$sel:webhook:PutWebhook' :: WebhookDefinition
webhook = WebhookDefinition
pWebhook_
}
putWebhook_tags :: Lens.Lens' PutWebhook (Prelude.Maybe [Tag])
putWebhook_tags :: Lens' PutWebhook (Maybe [Tag])
putWebhook_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutWebhook' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:PutWebhook' :: PutWebhook -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: PutWebhook
s@PutWebhook' {} Maybe [Tag]
a -> PutWebhook
s {$sel:tags:PutWebhook' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: PutWebhook) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
putWebhook_webhook :: Lens.Lens' PutWebhook WebhookDefinition
putWebhook_webhook :: Lens' PutWebhook WebhookDefinition
putWebhook_webhook = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutWebhook' {WebhookDefinition
webhook :: WebhookDefinition
$sel:webhook:PutWebhook' :: PutWebhook -> WebhookDefinition
webhook} -> WebhookDefinition
webhook) (\s :: PutWebhook
s@PutWebhook' {} WebhookDefinition
a -> PutWebhook
s {$sel:webhook:PutWebhook' :: WebhookDefinition
webhook = WebhookDefinition
a} :: PutWebhook)
instance Core.AWSRequest PutWebhook where
type AWSResponse PutWebhook = PutWebhookResponse
request :: (Service -> Service) -> PutWebhook -> Request PutWebhook
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 PutWebhook
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse PutWebhook)))
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 ListWebhookItem -> Int -> PutWebhookResponse
PutWebhookResponse'
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
"webhook")
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 PutWebhook where
hashWithSalt :: Int -> PutWebhook -> Int
hashWithSalt Int
_salt PutWebhook' {Maybe [Tag]
WebhookDefinition
webhook :: WebhookDefinition
tags :: Maybe [Tag]
$sel:webhook:PutWebhook' :: PutWebhook -> WebhookDefinition
$sel:tags:PutWebhook' :: PutWebhook -> Maybe [Tag]
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` WebhookDefinition
webhook
instance Prelude.NFData PutWebhook where
rnf :: PutWebhook -> ()
rnf PutWebhook' {Maybe [Tag]
WebhookDefinition
webhook :: WebhookDefinition
tags :: Maybe [Tag]
$sel:webhook:PutWebhook' :: PutWebhook -> WebhookDefinition
$sel:tags:PutWebhook' :: PutWebhook -> Maybe [Tag]
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf WebhookDefinition
webhook
instance Data.ToHeaders PutWebhook where
toHeaders :: PutWebhook -> 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
"CodePipeline_20150709.PutWebhook" ::
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 PutWebhook where
toJSON :: PutWebhook -> Value
toJSON PutWebhook' {Maybe [Tag]
WebhookDefinition
webhook :: WebhookDefinition
tags :: Maybe [Tag]
$sel:webhook:PutWebhook' :: PutWebhook -> WebhookDefinition
$sel:tags:PutWebhook' :: PutWebhook -> Maybe [Tag]
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"tags" 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 [Tag]
tags,
forall a. a -> Maybe a
Prelude.Just (Key
"webhook" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= WebhookDefinition
webhook)
]
)
instance Data.ToPath PutWebhook where
toPath :: PutWebhook -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery PutWebhook where
toQuery :: PutWebhook -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data PutWebhookResponse = PutWebhookResponse'
{
PutWebhookResponse -> Maybe ListWebhookItem
webhook :: Prelude.Maybe ListWebhookItem,
PutWebhookResponse -> Int
httpStatus :: Prelude.Int
}
deriving (PutWebhookResponse -> PutWebhookResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutWebhookResponse -> PutWebhookResponse -> Bool
$c/= :: PutWebhookResponse -> PutWebhookResponse -> Bool
== :: PutWebhookResponse -> PutWebhookResponse -> Bool
$c== :: PutWebhookResponse -> PutWebhookResponse -> Bool
Prelude.Eq, ReadPrec [PutWebhookResponse]
ReadPrec PutWebhookResponse
Int -> ReadS PutWebhookResponse
ReadS [PutWebhookResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutWebhookResponse]
$creadListPrec :: ReadPrec [PutWebhookResponse]
readPrec :: ReadPrec PutWebhookResponse
$creadPrec :: ReadPrec PutWebhookResponse
readList :: ReadS [PutWebhookResponse]
$creadList :: ReadS [PutWebhookResponse]
readsPrec :: Int -> ReadS PutWebhookResponse
$creadsPrec :: Int -> ReadS PutWebhookResponse
Prelude.Read, Int -> PutWebhookResponse -> ShowS
[PutWebhookResponse] -> ShowS
PutWebhookResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutWebhookResponse] -> ShowS
$cshowList :: [PutWebhookResponse] -> ShowS
show :: PutWebhookResponse -> String
$cshow :: PutWebhookResponse -> String
showsPrec :: Int -> PutWebhookResponse -> ShowS
$cshowsPrec :: Int -> PutWebhookResponse -> ShowS
Prelude.Show, forall x. Rep PutWebhookResponse x -> PutWebhookResponse
forall x. PutWebhookResponse -> Rep PutWebhookResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutWebhookResponse x -> PutWebhookResponse
$cfrom :: forall x. PutWebhookResponse -> Rep PutWebhookResponse x
Prelude.Generic)
newPutWebhookResponse ::
Prelude.Int ->
PutWebhookResponse
newPutWebhookResponse :: Int -> PutWebhookResponse
newPutWebhookResponse Int
pHttpStatus_ =
PutWebhookResponse'
{ $sel:webhook:PutWebhookResponse' :: Maybe ListWebhookItem
webhook = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:PutWebhookResponse' :: Int
httpStatus = Int
pHttpStatus_
}
putWebhookResponse_webhook :: Lens.Lens' PutWebhookResponse (Prelude.Maybe ListWebhookItem)
putWebhookResponse_webhook :: Lens' PutWebhookResponse (Maybe ListWebhookItem)
putWebhookResponse_webhook = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutWebhookResponse' {Maybe ListWebhookItem
webhook :: Maybe ListWebhookItem
$sel:webhook:PutWebhookResponse' :: PutWebhookResponse -> Maybe ListWebhookItem
webhook} -> Maybe ListWebhookItem
webhook) (\s :: PutWebhookResponse
s@PutWebhookResponse' {} Maybe ListWebhookItem
a -> PutWebhookResponse
s {$sel:webhook:PutWebhookResponse' :: Maybe ListWebhookItem
webhook = Maybe ListWebhookItem
a} :: PutWebhookResponse)
putWebhookResponse_httpStatus :: Lens.Lens' PutWebhookResponse Prelude.Int
putWebhookResponse_httpStatus :: Lens' PutWebhookResponse Int
putWebhookResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutWebhookResponse' {Int
httpStatus :: Int
$sel:httpStatus:PutWebhookResponse' :: PutWebhookResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: PutWebhookResponse
s@PutWebhookResponse' {} Int
a -> PutWebhookResponse
s {$sel:httpStatus:PutWebhookResponse' :: Int
httpStatus = Int
a} :: PutWebhookResponse)
instance Prelude.NFData PutWebhookResponse where
rnf :: PutWebhookResponse -> ()
rnf PutWebhookResponse' {Int
Maybe ListWebhookItem
httpStatus :: Int
webhook :: Maybe ListWebhookItem
$sel:httpStatus:PutWebhookResponse' :: PutWebhookResponse -> Int
$sel:webhook:PutWebhookResponse' :: PutWebhookResponse -> Maybe ListWebhookItem
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe ListWebhookItem
webhook
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus