Copyright | (c) Jacob Thomas Errington 2016 |
---|---|
License | MIT |
Maintainer | servant-github-webhook@mail.jerrington.me |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
The GitHub webhook machinery will attach three headers to the HTTP requests
that it fires: X-Github-Event
, X-Hub-Signature
, and X-Github-Delivery
.
The former two headers correspond with the GitHubEvent
and
GitHubSignedReqBody''
routing combinators. This library ignores the
X-Github-Delivery
header; if you would like to access its value, then use the
builtin Header
combinator from Servant.
Usage of the library is straightforward: protect routes with the GitHubEvent
combinator to ensure that the route is only reached for specific
RepoWebhookEvent
s, and replace any ReqBody
combinators you would write
under that route with GitHubSignedReqBody
. It is advised to always include a
GitHubSignedReqBody''
, as this is the only way you can be sure that it is
GitHub who is sending the request, and not a malicious user. If you don't care
about the request body, then simply use Aeson's Object
type as the
deserialization target -- GitHubSignedReqBody' key '[JSON] Object
-- and
ignore the Object
in the handler.
The GitHubSignedReqBody''
combinator makes use of the Servant Context
in
order to extract the signing key. This is the same key that must be entered in
the configuration of the webhook on GitHub. See GitHubKey'
for more details.
In order to support multiple keys on a per-route basis, the basic combinator
GitHubSignedReqBody''
takes as a type parameter as a key index. To use this,
create a datatype, e.g. KeyIndex
whose constructors identify the different
keys you will be using. Generally, this means one constructor per repository.
Use the DataKinds
extension to promote this datatype to a kind, and write an
instance of Reflect
for each promoted constructor of your datatype. Finally,
create a Context
containing GitHubKey'
whose wrapped function's domain is
the datatype you've built up. Thus, your function can determine which key to
retrieve.
Synopsis
- data GitHubSignedReqBody'' (proxy :: KProxy k) (key :: k) (list :: [*]) (result :: *)
- type GitHubSignedReqBody' (key :: k) = GitHubSignedReqBody'' (KProxy :: KProxy k) key
- type GitHubSignedReqBody = GitHubSignedReqBody' ()
- data GitHubEvent (events :: [RepoWebhookEvent])
- newtype GitHubKey' key result = GitHubKey {
- unGitHubKey :: key -> result -> IO (Maybe ByteString)
- type GitHubKey result = GitHubKey' () result
- gitHubKey :: IO ByteString -> GitHubKey result
- dynamicKey :: (Text -> IO (Maybe ByteString)) -> (result -> Maybe Text) -> GitHubKey result
- repositoryKey :: HasRepository result => (Text -> IO (Maybe ByteString)) -> GitHubKey result
- class HasRepository r
- newtype EventWithHookRepo e = EventWithHookRepo {
- eventOf :: e
- data RepoWebhookEvent
- = WebhookWildcardEvent
- | WebhookCheckRunEvent
- | WebhookCheckSuiteEvent
- | WebhookCommitCommentEvent
- | WebhookContentReferenceEvent
- | WebhookCreateEvent
- | WebhookDeleteEvent
- | WebhookDeployKeyEvent
- | WebhookDeploymentEvent
- | WebhookDeploymentStatusEvent
- | WebhookDownloadEvent
- | WebhookFollowEvent
- | WebhookForkEvent
- | WebhookForkApplyEvent
- | WebhookGitHubAppAuthorizationEvent
- | WebhookGistEvent
- | WebhookGollumEvent
- | WebhookInstallationEvent
- | WebhookInstallationRepositoriesEvent
- | WebhookIssueCommentEvent
- | WebhookIssuesEvent
- | WebhookLabelEvent
- | WebhookMarketplacePurchaseEvent
- | WebhookMemberEvent
- | WebhookMembershipEvent
- | WebhookMetaEvent
- | WebhookMilestoneEvent
- | WebhookOrganizationEvent
- | WebhookOrgBlockEvent
- | WebhookPageBuildEvent
- | WebhookPingEvent
- | WebhookProjectCardEvent
- | WebhookProjectColumnEvent
- | WebhookProjectEvent
- | WebhookPublicEvent
- | WebhookPullRequestEvent
- | WebhookPullRequestReviewEvent
- | WebhookPullRequestReviewCommentEvent
- | WebhookPushEvent
- | WebhookRegistryPackageEvent
- | WebhookReleaseEvent
- | WebhookRepositoryEvent
- | WebhookRepositoryImportEvent
- | WebhookRepositoryVulnerabilityAlertEvent
- | WebhookSecurityAdvisoryEvent
- | WebhookStarEvent
- | WebhookStatusEvent
- | WebhookTeamEvent
- | WebhookTeamAddEvent
- | WebhookWatchEvent
- data KProxy t = KProxy
- type Demote (a :: k) = Demote' (KProxy :: KProxy k)
- type family Demote' (kparam :: KProxy k) :: *
- class Reflect (a :: k) where
- parseHeaderMaybe :: FromHttpApiData a => ByteString -> Maybe a
- matchEvent :: RepoWebhookEvent -> ByteString -> Maybe RepoWebhookEvent
Servant combinators
data GitHubSignedReqBody'' (proxy :: KProxy k) (key :: k) (list :: [*]) (result :: *) Source #
A clone of Servant's ReqBody
combinator, except that it will also
verify the signature provided by GitHub in the X-Hub-Signature
header by
computing the SHA1 HMAC of the request body and comparing.
The use of this combinator will require that the router context contain an
appropriate GitHubKey'
entry. Specifically, the type parameter of
GitHubKey'
must correspond with Demote k
where k
is the kind of the
index key
used here. Consequently, it will be necessary to use
serveWithContext
instead of serve
.
Other routes are not tried upon the failure of this combinator, and a 401 response is generated.
Use of this datatype directly is discouraged, since the choice of the index
key
determines its kind k
and hence proxy
, which is . Instead, use
GitHubSignedReqBody'
, which computes the proxy
argument given just
key
. The proxy argument is necessary to avoid UndecidableInstances
for
the implementation of the HasServer
instance for the datatype.
Instances
(HasServer sublayout context, HasContextEntry context (GitHubKey' (Demote key) result), Reflect key, AllCTUnrender list result) => HasServer (GitHubSignedReqBody'' (KProxy :: KProxy k) key list result :> sublayout :: Type) context Source # | |
Defined in Servant.GitHub.Webhook route :: Proxy (GitHubSignedReqBody'' KProxy0 key list result :> sublayout) -> Context context -> Delayed env (Server (GitHubSignedReqBody'' KProxy0 key list result :> sublayout)) -> Router env # hoistServerWithContext :: Proxy (GitHubSignedReqBody'' KProxy0 key list result :> sublayout) -> Proxy context -> (forall x. m x -> n x) -> ServerT (GitHubSignedReqBody'' KProxy0 key list result :> sublayout) m -> ServerT (GitHubSignedReqBody'' KProxy0 key list result :> sublayout) n # | |
type ServerT (GitHubSignedReqBody'' (KProxy :: KProxy k) key list result :> sublayout :: Type) m Source # | |
Defined in Servant.GitHub.Webhook |
type GitHubSignedReqBody' (key :: k) = GitHubSignedReqBody'' (KProxy :: KProxy k) key Source #
Convenient synonym for GitHubSignedReqBody''
that computes its first
type argument given just the second one.
Use this type synonym if you are creating a webhook server to handle webhooks from multiple repositories, with different secret keys.
type GitHubSignedReqBody = GitHubSignedReqBody' () Source #
A convenient alias for a trivial key index.
USe this type synonym if you are creating a webhook server to handle only webhooks from a single repository, or for mutliple repositories using the same secret key.
data GitHubEvent (events :: [RepoWebhookEvent]) Source #
A routing combinator that succeeds only for a webhook request that matches
one of the given RepoWebhookEvent
given in the type-level list events
.
If the list contains WebhookWildcardEvent
, then all events will be
matched.
The combinator will require that its associated handler take a
RepoWebhookEvent
parameter, and the matched event will be passed to the
handler. This allows the handler to determine which event triggered it from
the list.
Other routes are tried if there is a mismatch.
Instances
(Reflect events, HasServer sublayout context) => HasServer (GitHubEvent events :> sublayout :: Type) context Source # | |
Defined in Servant.GitHub.Webhook type ServerT (GitHubEvent events :> sublayout) m :: Type # route :: Proxy (GitHubEvent events :> sublayout) -> Context context -> Delayed env (Server (GitHubEvent events :> sublayout)) -> Router env # hoistServerWithContext :: Proxy (GitHubEvent events :> sublayout) -> Proxy context -> (forall x. m x -> n x) -> ServerT (GitHubEvent events :> sublayout) m -> ServerT (GitHubEvent events :> sublayout) n # | |
type ServerT (GitHubEvent events :> sublayout :: Type) m Source # | |
Defined in Servant.GitHub.Webhook |
Security
newtype GitHubKey' key result Source #
A wrapper for an IO strategy to obtain the signing key for the webhook as
configured in GitHub. The strategy is executed each time the
GitHubSignedReqBody'
s routing logic is executed.
We allow the use of IO
here so that you can fetch the key from a cache or
a database. If the key is a constant or read only once, just use pure
.
The type key
used here must correspond with
where Demote
kk
is the
kind whose types are used as indices in GitHubSignedReqBody'
.
If you don't care about indices and just want to write a webhook using a
global key, see GitHubKey'
which fixes key
to ()
and use gitHubKey
,
which fills the newtype with a constant function.
GitHubKey | |
|
type GitHubKey result = GitHubKey' () result Source #
A synonym for strategies producing so-called global keys, in which the
key index is simply ()
.
gitHubKey :: IO ByteString -> GitHubKey result Source #
Smart constructor for GitHubKey'
, for a so-called global key.
dynamicKey :: (Text -> IO (Maybe ByteString)) -> (result -> Maybe Text) -> GitHubKey result Source #
dynamicKey keyLookup keyIdLookup
acquires the key identifier, such as
repository or user name, from the result then uses keyLookup
to acquire the
key (or Nothing
).
Dynamic keys allow servers to specify per-user repository keys. This limits the impact of compromized keys and allows the server to acquire the key from external sources, such as a live configuration or per-user rows in a database.
repositoryKey :: HasRepository result => (Text -> IO (Maybe ByteString)) -> GitHubKey result Source #
class HasRepository r Source #
The HasRepository class helps extract the full (unique) "name/repo" of a
repository, allowing easy lookup of a per-repository key or, using takeWhile
(='')
, lookup of per user keys.
getFullName
Instances
HasRepository Object Source # | |
Defined in Servant.GitHub.Webhook getFullName :: Object -> Maybe Text | |
HasRepository Value Source # | |
Defined in Servant.GitHub.Webhook getFullName :: Value -> Maybe Text | |
EventHasRepo e => HasRepository (EventWithHookRepo e) Source # | |
Defined in Servant.GitHub.Webhook getFullName :: EventWithHookRepo e -> Maybe Text |
newtype EventWithHookRepo e Source #
For use with 'github-webhooks' package types. Routes would look like:
api = "github-webevent" :> :> GitHubSignedReqBody '[JSON] (EventWithHookRepo IssuesEvent) :> Post '[JSON] ()
And the handler would unwrap the event:
handler :: EventWithHookRepo IssuesEvent -> Handler () handler (eventOf -> e) = -- ... expr handling e :: IssuesEvent ...
EventWithHookRepo | |
|
Instances
FromJSON e => FromJSON (EventWithHookRepo e) Source # | |
Defined in Servant.GitHub.Webhook parseJSON :: Value -> Parser (EventWithHookRepo e) # parseJSONList :: Value -> Parser [EventWithHookRepo e] # | |
EventHasRepo e => HasRepository (EventWithHookRepo e) Source # | |
Defined in Servant.GitHub.Webhook getFullName :: EventWithHookRepo e -> Maybe Text |
Reexports
We reexport a few datatypes that are typically needed to use the library.
data RepoWebhookEvent #
Instances
A concrete, promotable proxy type, for use at the kind level There are no instances for this because it is intended at the kind level only
Implementation details
Type-level programming machinery
type family Demote' (kparam :: KProxy k) :: * Source #
Type function that reflects a kind to a type.
class Reflect (a :: k) where Source #
Class of types that can be reflected to values.
Instances
Stringy stuff
parseHeaderMaybe :: FromHttpApiData a => ByteString -> Maybe a Source #
Helper that parses a header using a FromHttpApiData
instance and
discards the parse error message if any.
matchEvent :: RepoWebhookEvent -> ByteString -> Maybe RepoWebhookEvent Source #
Determines whether a given webhook event matches a given raw
representation of one. The result is Nothing
if there is no match. This
function accounts for the WebhookWildcardEvent
matching everything, so it
returns the result of parsing the raw representation when trying to match
against the wildcard.