pusher-http-haskell-1.5.1.11: Haskell client library for the Pusher HTTP API

Copyright(c) Will Sewell 2016
LicenseMIT
Maintainerme@willsewell.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Network.Pusher

Contents

Description

Exposes the functions necessary for interacting with the Pusher HTTP API, as well as functions for generating auth signatures for private and presence channels.

First create a Pusher data structure with your Pusher Credentials, and then call the functions defined in this module to make the HTTP requests.

If any of the requests fail, the return values of the functions will result in a Left PusherError when run.

An example of how you would use these functions:

  let
    credentials = Credentials
      { credentialsAppID     = 123
      , credentialsAppKey    = "wrd12344rcd234"
      , credentialsAppSecret = "124df34d545v"
      , credentialsCluster   = Nothing
      }
  pusher <- getPusher credentials

  triggerRes <-
    trigger pusher [Channel Public "my-channel"] "my-event" "my-data" Nothing

  case triggerRes of
    Left e -> putStrLn $ displayException e
    Right resp -> print resp

  -- import qualified Data.HashMap.Strict as H
  -- import qualified Data.Aeson          as A
  let
    -- A Firebase Cloud Messaging notification payload
    fcmObject = H.fromList [("notification", A.Object $ H.fromList
                                [("title", A.String "a title")
                                ,("body" , A.String "some text")
                                ,("icon" , A.String "logo.png")
                                ]
                            )]
    Just interest = mkInterest "some-interest"

    -- A Pusher notification
    notification = Notification
      { notificationInterest     = interest
      , notificationWebhookURL   = Nothing
      , notificationWebhookLevel = Nothing
      , notificationAPNSPayload  = Nothing
      , notificationGCMPayload   = Nothing
      , notificationFCMPayload   = Just $ FCMPayload fcmObject
      }

  notifyRes <- notify pusher notification

There are simple working examples in the example/ directory.

See https://pusher.com/docs/rest_api for more detail on the HTTP requests.

Synopsis

Data types

Pusher config type

data Pusher Source #

All the required configuration needed to interact with the API.

newtype Cluster Source #

The cluster the current app resides on. Common clusters include: mt1,eu,ap1,ap2.

Constructors

Cluster 

Fields

Instances
FromJSON Cluster Source # 
Instance details

Defined in Network.Pusher.Data

getPusher :: MonadIO m => Credentials -> m Pusher Source #

Use this to get an instance Pusher. This will fill in the host and path automatically.

getPusherWithHost :: MonadIO m => Text -> Text -> Credentials -> m Pusher Source #

Get a Pusher instance that uses a specific API endpoint.

getPusherWithConnManager :: Manager -> Maybe Text -> Maybe Text -> Credentials -> Pusher Source #

Get a Pusher instance with a given connection manager. This can be useful if you want to share a connection with your application code.

Channels

data Channel Source #

The channel name (not including the channel type prefix) and its type.

Instances
Eq Channel Source # 
Instance details

Defined in Network.Pusher.Data

Methods

(==) :: Channel -> Channel -> Bool #

(/=) :: Channel -> Channel -> Bool #

Show Channel Source # 
Instance details

Defined in Network.Pusher.Data

Generic Channel Source # 
Instance details

Defined in Network.Pusher.Data

Associated Types

type Rep Channel :: Type -> Type #

Methods

from :: Channel -> Rep Channel x #

to :: Rep Channel x -> Channel #

Hashable Channel Source # 
Instance details

Defined in Network.Pusher.Data

Methods

hashWithSalt :: Int -> Channel -> Int #

hash :: Channel -> Int #

FromJSON Channel Source # 
Instance details

Defined in Network.Pusher.Data

type Rep Channel Source # 
Instance details

Defined in Network.Pusher.Data

type Rep Channel = D1 (MetaData "Channel" "Network.Pusher.Data" "pusher-http-haskell-1.5.1.11-3i36fXmIghVJIFXFiRt4JB" False) (C1 (MetaCons "Channel" PrefixI True) (S1 (MetaSel (Just "channelType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ChannelType) :*: S1 (MetaSel (Just "channelName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ChannelName)))

data ChannelType Source #

The possible types of Pusher channe.

Constructors

Public 
Private 
Presence 
Instances
Eq ChannelType Source # 
Instance details

Defined in Network.Pusher.Data

Show ChannelType Source # 
Instance details

Defined in Network.Pusher.Data

Generic ChannelType Source # 
Instance details

Defined in Network.Pusher.Data

Associated Types

type Rep ChannelType :: Type -> Type #

Hashable ChannelType Source # 
Instance details

Defined in Network.Pusher.Data

type Rep ChannelType Source # 
Instance details

Defined in Network.Pusher.Data

type Rep ChannelType = D1 (MetaData "ChannelType" "Network.Pusher.Data" "pusher-http-haskell-1.5.1.11-3i36fXmIghVJIFXFiRt4JB" False) (C1 (MetaCons "Public" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Private" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Presence" PrefixI False) (U1 :: Type -> Type)))

parseChannel :: Text -> Channel Source #

Convert string representation, e.g. private-chan into the datatype.

Events

Notifications

data Interest Source #

Up to 164 characters where each character is ASCII upper or lower case, a number or one of _=@,.;

Note: hyphen - is NOT valid as it is reserved for the possibility of marking interest names with prefixes such as private- or presence-.

Instances
Eq Interest Source # 
Instance details

Defined in Network.Pusher.Data

Show Interest Source # 
Instance details

Defined in Network.Pusher.Data

ToJSON Interest Source # 
Instance details

Defined in Network.Pusher.Data

FromJSON Interest Source # 
Instance details

Defined in Network.Pusher.Data

type WebhookURL = Text Source #

URL to which pusher will send information about sent push notifications.

data WebhookLevel Source #

Level of detail sent to WebhookURL. Defaults to Info.

Constructors

Info

Errors only

Debug

Everything

data APNSPayload Source #

Apple push notification service payload.

Constructors

APNSPayload Object 

data GCMPayload Source #

Google Cloud Messaging payload.

Constructors

GCMPayload Object 

data FCMPayload Source #

Firebase Cloud Messaging payload.

Constructors

FCMPayload Object 

HTTP Requests

Trigger events

trigger Source #

Arguments

:: MonadIO m 
=> Pusher 
-> [Channel]

The list of channels to trigger to.

-> Event 
-> EventData

Often encoded JSON.

-> Maybe SocketID

An optional socket ID of a connection you wish to exclude.

-> m (Either PusherError ()) 

Trigger an event to one or more channels.

Channel queries

channels Source #

Arguments

:: MonadIO m 
=> Pusher 
-> Maybe ChannelType

Filter by the type of channel.

-> Text

A channel prefix you wish to filter on.

-> ChannelsInfoQuery

Data you wish to query for, currently just the user count.

-> m (Either PusherError ChannelsInfo)

The returned data.

Query a list of channels for information.

channel Source #

Arguments

:: MonadIO m 
=> Pusher 
-> Channel 
-> ChannelInfoQuery

Can query user count and also subscription count (if enabled).

-> m (Either PusherError FullChannelInfo) 

Query for information on a single channel.

users :: MonadIO m => Pusher -> Channel -> m (Either PusherError Users) Source #

Get a list of users in a presence channel.

Push notifications

notify :: MonadIO m => Pusher -> Notification -> m (Either PusherError ()) Source #

Send a push notification.

Authentication

type AuthString = ByteString Source #

The bytestring to sign with the app secret to create a signature from.

type AuthSignature = ByteString Source #

A Pusher auth signature.

authenticatePresence :: ToJSON a => Credentials -> SocketID -> Channel -> a -> AuthSignature Source #

Generate an auth signature of the form "app_key:auth_sig" for a user of a presence channel.

authenticatePrivate :: Credentials -> SocketID -> Channel -> AuthSignature Source #

Generate an auth signature of the form "app_key:auth_sig" for a user of a private channel.

Errors

data PusherError Source #

Constructors

PusherArgumentError Text

Data from the caller is not valid.

PusherNon200ResponseError Text

Received non 200 response code from Pusher.

PusherInvalidResponseError Text

Received unexpected data from Pusher.

Webhooks

parseWebhookPayload :: Pusher -> [(ByteString, ByteString)] -> ByteString -> Maybe WebhookPayload Source #

Parse webhooks from a list of HTTP headers and a HTTP body given their AppKey matches the one in our Pusher credentials and the webhook is correctly encrypted by the corresponding AppSecret.

data WebhookEv Source #

A WebhookEv is one of several events Pusher may send to your server in response to events your users may trigger.

Constructors

ChannelOccupiedEv

A channel has become occupied. There is > 1 subscriber.

Fields

ChannelVacatedEv

A channel has become vacated. There are 0 subscribers.

Fields

MemberAddedEv

A new user has subscribed to a presence channel.

MemberRemovedEv

A user has unsubscribed from a presence channel.

ClientEv

A client has sent a named client event with some json body. They have a SocketID and a User if they were in a presence channel.

Instances
Eq WebhookEv Source # 
Instance details

Defined in Network.Pusher.Webhook

Show WebhookEv Source # 
Instance details

Defined in Network.Pusher.Webhook

FromJSON WebhookEv Source # 
Instance details

Defined in Network.Pusher.Webhook

data WebhookPayload Source #

Constructors

WebhookPayload 

Fields

data Webhooks Source #

A Webhook is received by POST request from Pusher to notify your server of a number of WebhookEvs. Multiple events are received under the same timestamp if batch events is enabled.

Constructors

Webhooks 
Instances
Eq Webhooks Source # 
Instance details

Defined in Network.Pusher.Webhook

Show Webhooks Source # 
Instance details

Defined in Network.Pusher.Webhook

FromJSON Webhooks Source # 
Instance details

Defined in Network.Pusher.Webhook

parseAppKeyHdr :: ByteString -> ByteString -> Maybe AppKey Source #

Given a HTTP Header and its associated value, parse an AppKey.

parseAuthSignatureHdr :: ByteString -> ByteString -> Maybe AuthSignature Source #

Given a HTTP Header and its associated value, parse a AuthSignature.

parseWebhooksBody :: ByteString -> Maybe Webhooks Source #

Given a HTTP body, parse the contained webhooks.

verifyWebhooksBody :: AppSecret -> AuthSignature -> ByteString -> Bool Source #

Does a webhook body hash with our secret key to the given signature?

parseWebhookPayloadWith :: (AppKey -> Maybe AppSecret) -> [(ByteString, ByteString)] -> ByteString -> Maybe WebhookPayload Source #

Given a list of http header key:values, a http body and a lookup function for an apps secret, parse and validate a potential webhook payload.