fb-2.1.1.1: Bindings to Facebook's API.
Safe HaskellNone
LanguageHaskell2010

Facebook

Synopsis

FacebookT monad transformer

data FacebookT auth m a Source #

FacebookT auth m a is this library's monad transformer. Contains information needed to issue commands and queries to Facebook. The phantom type auth may be either Auth (you have supplied your Credentials) or NoAuth (you have not supplied any Credentials).

Instances

Instances details
MonadBase b m => MonadBase b (FacebookT auth m) Source # 
Instance details

Defined in Facebook.Monad

Methods

liftBase :: b α -> FacebookT auth m α #

MonadTrans (FacebookT auth) Source # 
Instance details

Defined in Facebook.Monad

Methods

lift :: Monad m => m a -> FacebookT auth m a #

Monad m => Monad (FacebookT auth m) Source # 
Instance details

Defined in Facebook.Monad

Methods

(>>=) :: FacebookT auth m a -> (a -> FacebookT auth m b) -> FacebookT auth m b #

(>>) :: FacebookT auth m a -> FacebookT auth m b -> FacebookT auth m b #

return :: a -> FacebookT auth m a #

Functor m => Functor (FacebookT auth m) Source # 
Instance details

Defined in Facebook.Monad

Methods

fmap :: (a -> b) -> FacebookT auth m a -> FacebookT auth m b #

(<$) :: a -> FacebookT auth m b -> FacebookT auth m a #

MonadFix m => MonadFix (FacebookT auth m) Source # 
Instance details

Defined in Facebook.Monad

Methods

mfix :: (a -> FacebookT auth m a) -> FacebookT auth m a #

MonadFail m => MonadFail (FacebookT auth m) Source # 
Instance details

Defined in Facebook.Monad

Methods

fail :: String -> FacebookT auth m a #

Applicative m => Applicative (FacebookT auth m) Source # 
Instance details

Defined in Facebook.Monad

Methods

pure :: a -> FacebookT auth m a #

(<*>) :: FacebookT auth m (a -> b) -> FacebookT auth m a -> FacebookT auth m b #

liftA2 :: (a -> b -> c) -> FacebookT auth m a -> FacebookT auth m b -> FacebookT auth m c #

(*>) :: FacebookT auth m a -> FacebookT auth m b -> FacebookT auth m b #

(<*) :: FacebookT auth m a -> FacebookT auth m b -> FacebookT auth m a #

Alternative m => Alternative (FacebookT auth m) Source # 
Instance details

Defined in Facebook.Monad

Methods

empty :: FacebookT auth m a #

(<|>) :: FacebookT auth m a -> FacebookT auth m a -> FacebookT auth m a #

some :: FacebookT auth m a -> FacebookT auth m [a] #

many :: FacebookT auth m a -> FacebookT auth m [a] #

MonadPlus m => MonadPlus (FacebookT auth m) Source # 
Instance details

Defined in Facebook.Monad

Methods

mzero :: FacebookT auth m a #

mplus :: FacebookT auth m a -> FacebookT auth m a -> FacebookT auth m a #

MonadIO m => MonadIO (FacebookT auth m) Source # 
Instance details

Defined in Facebook.Monad

Methods

liftIO :: IO a -> FacebookT auth m a #

MonadUnliftIO m => MonadUnliftIO (FacebookT auth m) Source # 
Instance details

Defined in Facebook.Monad

Methods

withRunInIO :: ((forall a. FacebookT auth m a -> IO a) -> IO b) -> FacebookT auth m b #

(MonadResource m, MonadBase IO m) => MonadResource (FacebookT auth m) Source # 
Instance details

Defined in Facebook.Monad

Methods

liftResourceT :: ResourceT IO a -> FacebookT auth m a #

MonadThrow m => MonadThrow (FacebookT auth m) Source # 
Instance details

Defined in Facebook.Monad

Methods

throwM :: Exception e => e -> FacebookT auth m a #

MonadLogger m => MonadLogger (FacebookT auth m) Source #

Since fb-0.14.8.

Instance details

Defined in Facebook.Monad

Methods

monadLoggerLog :: ToLogStr msg => Loc -> LogSource -> LogLevel -> msg -> FacebookT auth m () #

runFacebookT Source #

Arguments

:: MonadIO m 
=> Credentials

Your app's credentials.

-> Manager

Connection manager (see withManager).

-> FacebookT Auth m a 
-> m a 

Run a computation in the FacebookT monad transformer with your credentials.

runNoAuthFacebookT Source #

Arguments

:: MonadIO m 
=> Manager

Connection manager (see withManager).

-> FacebookT NoAuth m a 
-> m a 

Run a computation in the FacebookT monad without credentials.

mapFacebookT :: (m a -> n b) -> FacebookT anyAuth m a -> FacebookT anyAuth n b Source #

Transform the computation inside a FacebookT.

data Auth Source #

Phantom type stating that you have provided your Credentials and thus have access to the whole API.

data NoAuth Source #

Phantom type stating that you have not provided your Credentials. This means that you'll be limited about which APIs you'll be able use.

Authorization and Authentication

Credentials

data Credentials Source #

Credentials that you get for your app when you register on Facebook.

Constructors

Credentials 

Fields

Access token

data AccessToken kind where Source #

An access token. While you can make some API calls without an access token, many require an access token and some will give you more information with an appropriate access token.

There are two kinds of access tokens:

User access token
An access token obtained after an user accepts your application. Let's you access more information about that user and act on their behalf (depending on which permissions you've asked for).
App access token
An access token that allows you to take administrative actions for your application.

These two kinds of access tokens are distinguished by the phantom type on AccessToken, which can be UserKind or AppKind.

Instances

Instances details
Eq (AccessToken kind) Source # 
Instance details

Defined in Facebook.Types

Methods

(==) :: AccessToken kind -> AccessToken kind -> Bool #

(/=) :: AccessToken kind -> AccessToken kind -> Bool #

Ord (AccessToken kind) Source # 
Instance details

Defined in Facebook.Types

Methods

compare :: AccessToken kind -> AccessToken kind -> Ordering #

(<) :: AccessToken kind -> AccessToken kind -> Bool #

(<=) :: AccessToken kind -> AccessToken kind -> Bool #

(>) :: AccessToken kind -> AccessToken kind -> Bool #

(>=) :: AccessToken kind -> AccessToken kind -> Bool #

max :: AccessToken kind -> AccessToken kind -> AccessToken kind #

min :: AccessToken kind -> AccessToken kind -> AccessToken kind #

Show (AccessToken kind) Source # 
Instance details

Defined in Facebook.Types

Methods

showsPrec :: Int -> AccessToken kind -> ShowS #

show :: AccessToken kind -> String #

showList :: [AccessToken kind] -> ShowS #

ToJSON (AccessToken kind) Source #

Synonym for mappend.

Since 0.14.9. Not a Facebook JSON format, but a custom fb format for convenience if you need to serialize access tokens.

Instance details

Defined in Facebook.Types

ParseAccessToken kind => FromJSON (AccessToken kind) Source #

Since 0.14.9. Parses the format that ToJSON produces. Note that you need to statically decide whether you want to parse a user access token or an app access token.

Instance details

Defined in Facebook.Types

type AccessTokenData = Text Source #

The access token data that is passed to Facebook's API calls.

hasExpired :: (Functor m, MonadIO m) => AccessToken anyKind -> m Bool Source #

True if the access token has expired, otherwise False.

isValid :: (MonadResource m, MonadUnliftIO m) => AccessToken anyKind -> FacebookT anyAuth m Bool Source #

True if the access token is valid. An expired access token is not valid (see hasExpired). However, a non-expired access token may not be valid as well. For example, in the case of an user access token, they may have changed their password, logged out from Facebook or blocked your app.

setApiVersion :: MonadIO m => ApiVersion -> FacebookT anyAuth m () Source #

Set the Graph API version.

getApiVersion :: MonadIO m => FacebookT anyAuth m ApiVersion Source #

Get the Graph API version.

App access token

data AppKind Source #

Phantom type used mark an AccessToken as an app access token.

User access token

data UserKind Source #

Phantom type used mark an AccessToken as an user access token.

type RedirectUrl = Text Source #

URL where the user is redirected to after Facebook authenticates the user authorizes your application. This URL should be inside the domain registered for your Facebook application.

data Permission Source #

A permission that is asked for the user when he authorizes your app. Please refer to Facebook's documentation at https://developers.facebook.com/docs/reference/api/permissions/ to see which permissions are available.

This is a newtype of Text that supports only IsString. This means that to create a Permission you should use the OverloadedStrings language extension. For example,

{-# LANGUAGE OverloadedStrings #-}

perms :: [Permission]
perms = ["user_about_me", "email", "offline_access"]

Instances

Instances details
Eq Permission Source # 
Instance details

Defined in Facebook.Auth

Ord Permission Source # 
Instance details

Defined in Facebook.Auth

Show Permission Source # 
Instance details

Defined in Facebook.Auth

IsString Permission Source # 
Instance details

Defined in Facebook.Auth

SimpleType Permission Source #

Permission is a newtype of Text

Instance details

Defined in Facebook.Graph

getUserAccessTokenStep1 :: (Monad m, MonadIO m) => RedirectUrl -> [Permission] -> FacebookT Auth m Text Source #

The first step to get an user access token. Returns the Facebook URL you should redirect you user to. Facebook will authenticate the user, authorize your app and then redirect the user back into the provider RedirectUrl.

getUserAccessTokenStep2 Source #

Arguments

:: (MonadResource m, MonadUnliftIO m, MonadThrow m, MonadIO m) 
=> RedirectUrl

Should be exactly the same as in getUserAccessTokenStep1.

-> [Argument]

Query parameters.

-> FacebookT Auth m UserAccessToken 

The second step to get an user access token. If the user is successfully authenticate and they authorize your application, then they'll be redirected back to the RedirectUrl you've passed to getUserAccessTokenStep1. You should take the request query parameters passed to your RedirectUrl and give to this function that will complete the user authentication flow and give you an UserAccessToken.

getUserLogoutUrl Source #

Arguments

:: Monad m 
=> UserAccessToken

The user's access token.

-> RedirectUrl

URL the user should be directed to in your site domain.

-> FacebookT Auth m Text

Logout URL in https://www.facebook.com/ (or on https://www.beta.facebook.com/ when using the beta tier).

The URL an user should be redirected to in order to log them out of their Facebook session. Facebook will then redirect the user to the provided URL after logging them out. Note that, at the time of this writing, Facebook's policies require you to log the user out of Facebook when they ask to log out of your site.

Note also that Facebook may refuse to redirect the user to the provided URL if their user access token is invalid. In order to prevent this bug, we suggest that you use isValid before redirecting the user to the URL provided by getUserLogoutUrl since this function doesn't do any validity checks.

extendUserAccessToken :: (MonadResource m, MonadUnliftIO m, MonadThrow m, MonadIO m) => UserAccessToken -> FacebookT Auth m (Either FacebookException UserAccessToken) Source #

Extend the expiration time of an user access token (see https://developers.facebook.com/docs/offline-access-deprecation/, https://developers.facebook.com/roadmap/offline-access-removal/). Only short-lived user access tokens may extended into long-lived user access tokens, you must get a new short-lived user access token if you need to extend a long-lived one. Returns Left exc if there is an error while extending, or Right token with the new user access token (which could have the same data and expiration time as before, but you can't assume this). Note that expired access tokens can't be extended, only valid tokens.

debugToken Source #

Arguments

:: (MonadResource m, MonadUnliftIO m, MonadThrow m) 
=> AppAccessToken

Your app access token.

-> AccessTokenData

The access token you want to debug.

-> FacebookT Auth m DebugToken 

Get detailed information about an access token.

data DebugToken Source #

Detailed information about an access token (cf. debugToken).

Instances

Instances details
Eq DebugToken Source # 
Instance details

Defined in Facebook.Auth

Ord DebugToken Source # 
Instance details

Defined in Facebook.Auth

Show DebugToken Source # 
Instance details

Defined in Facebook.Auth

FromJSON DebugToken Source #

Note: this instance always sets dtAccessToken to Nothing, but debugToken will update this field before returning the final DebugToken. This is done because we need the AccessTokenData, which is not part of FB's response.

Instance details

Defined in Facebook.Auth

Signed requests

parseSignedRequest Source #

Arguments

:: (FromJSON a, Monad m, MonadIO m) 
=> ByteString

Encoded Facebook signed request

-> FacebookT Auth m (Maybe a) 

Parses a Facebook signed request (https://developers.facebook.com/docs/authentication/signed_request/), verifies its authencity and integrity using the HMAC and decodes its JSON object.

makeAppSecretProof Source #

Arguments

:: Credentials

App credentials

-> Maybe (AccessToken anyKind) 
-> SimpleQuery 

Make an appsecret_proof in case the given credentials access token is a user access token. See: https://developers.facebook.com/docs/graph-api/securing-requests/#appsecret_proof

Facebook's Graph API

User

data User Source #

A Facebook user profile (see https://developers.facebook.com/docs/reference/api/user/).

NOTE: We still don't support all fields supported by Facebook. Please fill an issue if you need access to any other fields.

Instances

Instances details
Eq User Source # 
Instance details

Defined in Facebook.Object.User

Methods

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

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

Ord User Source # 
Instance details

Defined in Facebook.Object.User

Methods

compare :: User -> User -> Ordering #

(<) :: User -> User -> Bool #

(<=) :: User -> User -> Bool #

(>) :: User -> User -> Bool #

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

max :: User -> User -> User #

min :: User -> User -> User #

Read User Source # 
Instance details

Defined in Facebook.Object.User

Show User Source # 
Instance details

Defined in Facebook.Object.User

Methods

showsPrec :: Int -> User -> ShowS #

show :: User -> String #

showList :: [User] -> ShowS #

FromJSON User Source # 
Instance details

Defined in Facebook.Object.User

type UserId = Id Source #

A Facebook user ID such as 1008905713901.

data Gender Source #

An user's gender.

Constructors

Male 
Female 

Instances

Instances details
Enum Gender Source # 
Instance details

Defined in Facebook.Object.User

Eq Gender Source # 
Instance details

Defined in Facebook.Object.User

Methods

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

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

Ord Gender Source # 
Instance details

Defined in Facebook.Object.User

Read Gender Source # 
Instance details

Defined in Facebook.Object.User

Show Gender Source # 
Instance details

Defined in Facebook.Object.User

ToJSON Gender Source # 
Instance details

Defined in Facebook.Object.User

FromJSON Gender Source # 
Instance details

Defined in Facebook.Object.User

getUser Source #

Arguments

:: (MonadResource m, MonadUnliftIO m, MonadThrow m) 
=> UserId

User ID or "me".

-> [Argument]

Arguments to be passed to Facebook.

-> Maybe UserAccessToken

Optional user access token.

-> FacebookT anyAuth m User 

Get an user using his user ID. The user access token is optional, but when provided more information can be returned back by Facebook. The user ID may be "me", in which case you must provide an user access token and information about the token's owner is given.

searchUsers :: (MonadResource m, MonadUnliftIO m, MonadThrow m) => Text -> [Argument] -> Maybe UserAccessToken -> FacebookT anyAuth m (Pager User) Source #

Search users by keyword.

getUserCheckins Source #

Arguments

:: (MonadResource m, MonadUnliftIO m, MonadThrow m) 
=> UserId

User ID or "me".

-> [Argument]

Arguments to be passed to Facebook.

-> UserAccessToken

User access token.

-> FacebookT anyAuth m (Pager Checkin) 

Get a list of check-ins made by a given user.

data Friend Source #

A friend connection of a User.

Constructors

Friend 

Instances

Instances details
Eq Friend Source # 
Instance details

Defined in Facebook.Object.User

Methods

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

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

Ord Friend Source # 
Instance details

Defined in Facebook.Object.User

Read Friend Source # 
Instance details

Defined in Facebook.Object.User

Show Friend Source # 
Instance details

Defined in Facebook.Object.User

FromJSON Friend Source # 
Instance details

Defined in Facebook.Object.User

getUserFriends Source #

Arguments

:: (MonadResource m, MonadUnliftIO m, MonadThrow m) 
=> UserId

User ID or "me".

-> [Argument]

Arguments to be passed to Facebook.

-> UserAccessToken

User access token.

-> FacebookT anyAuth m (Pager Friend) 

Get the list of friends of the given user.

getUserFriendLists Source #

Arguments

:: (MonadResource m, MonadUnliftIO m, MonadThrow m) 
=> UserId

User ID or "me".

-> [Argument]

Arguments to be passed to Facebook.

-> UserAccessToken

User access token.

-> FacebookT anyAuth m (Pager FriendList) 

Get the friend lists of the given user.

Page

data Page Source #

A Facebook page (see https://developers.facebook.com/docs/reference/api/page/).

NOTE: Does not yet support all fields. Please file an issue if you need any other fields.

Instances

Instances details
Eq Page Source # 
Instance details

Defined in Facebook.Object.Page

Methods

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

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

Ord Page Source # 
Instance details

Defined in Facebook.Object.Page

Methods

compare :: Page -> Page -> Ordering #

(<) :: Page -> Page -> Bool #

(<=) :: Page -> Page -> Bool #

(>) :: Page -> Page -> Bool #

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

max :: Page -> Page -> Page #

min :: Page -> Page -> Page #

Read Page Source # 
Instance details

Defined in Facebook.Object.Page

Show Page Source # 
Instance details

Defined in Facebook.Object.Page

Methods

showsPrec :: Int -> Page -> ShowS #

show :: Page -> String #

showList :: [Page] -> ShowS #

FromJSON Page Source # 
Instance details

Defined in Facebook.Object.Page

getPage Source #

Arguments

:: (MonadResource m, MonadUnliftIO m, MonadThrow m) 
=> Id

Page ID

-> [Argument]

Arguments to be passed to Facebook

-> Maybe UserAccessToken

Optional user access token

-> FacebookT anyAuth m Page 

Get a page using its ID. The user access token is optional.

getPage_ Source #

Arguments

:: (MonadResource m, MonadUnliftIO m, MonadThrow m) 
=> Id

Page ID

-> [Argument]

Arguments to be passed to Facebook

-> Maybe AppAccessToken

Optional user access token

-> FacebookT anyAuth m Page 

Get a page using its ID. The user access token is optional.

searchPages Source #

Arguments

:: (MonadResource m, MonadUnliftIO m, MonadThrow m) 
=> Text

Keyword to search for

-> [Argument]

Arguments to pass to Facebook

-> Maybe UserAccessToken

Optional user access token

-> FacebookT anyAuth m (Pager Page) 

Search pages by keyword. The user access token is optional.

Actions

data Action Source #

An action of your app. Please refer to Facebook's documentation at https://developers.facebook.com/docs/opengraph/keyconcepts/#actions-objects to see how you can create actions.

This is a newtype of Text that supports only IsString. This means that to create an Action you should use the OverloadedStrings language extension. For example,

{-# LANGUAGE OverloadedStrings #-}

foo token = do
  ...
  createAction "cook" [...] token

Instances

Instances details
Eq Action Source #

Since 0.7.1

Instance details

Defined in Facebook.Object.Action

Methods

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

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

Ord Action Source #

Since 0.7.1

Instance details

Defined in Facebook.Object.Action

Read Action Source #

Since 0.7.1

Instance details

Defined in Facebook.Object.Action

Show Action Source # 
Instance details

Defined in Facebook.Object.Action

IsString Action Source # 
Instance details

Defined in Facebook.Object.Action

Methods

fromString :: String -> Action #

createAction Source #

Arguments

:: (MonadResource m, MonadUnliftIO m, MonadThrow m, MonadIO m) 
=> Action

Action kind to be created.

-> [Argument]

Arguments of the action.

-> Maybe AppAccessToken

Optional app access token (optional with respect to this library, since you can't make this mandatory by changing the settings of your action on Facebook).

-> UserAccessToken

Required user access token.

-> FacebookT Auth m Id 

Creates an Open Graph action on the user's timeline. Returns the Id of the newly created action. For example:

now <- liftIO getCurrentTime
createAction "cook"
             [ "recipe" #= "http://example.com/cookie.html"
             , "when"   #= now ]
             token

Checkins

data Checkin Source #

A Facebook check-in (see https://developers.facebook.com/docs/reference/api/checkin/).

NOTE: We still don't support all fields supported by Facebook. Please fill an issue if you need access to any other fields.

Instances

Instances details
Eq Checkin Source # 
Instance details

Defined in Facebook.Object.Checkin

Methods

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

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

Ord Checkin Source # 
Instance details

Defined in Facebook.Object.Checkin

Read Checkin Source # 
Instance details

Defined in Facebook.Object.Checkin

Show Checkin Source # 
Instance details

Defined in Facebook.Object.Checkin

FromJSON Checkin Source # 
Instance details

Defined in Facebook.Object.Checkin

getCheckin Source #

Arguments

:: (MonadResource m, MonadUnliftIO m, MonadThrow m) 
=> Id

Checkin ID.

-> [Argument]

Arguments to be passed to Facebook.

-> Maybe UserAccessToken

Optional user access token.

-> FacebookT anyAuth m Checkin 

Get a checkin from its ID. The user access token is optional, but when provided more information can be returned back by Facebook.

createCheckin Source #

Arguments

:: (MonadResource m, MonadUnliftIO m, MonadThrow m) 
=> Id

Place ID.

-> GeoCoordinates

Coordinates.

-> [Argument]

Other arguments of the action.

-> UserAccessToken

Required user access token.

-> FacebookT Auth m Id 

Creates a 'check-in' and returns its ID. Place and coordinates are both required by Facebook.

Order

type OrderId = Id Source #

Order Id type.

data OrderApplication Source #

A trimmed down version of Facebook Application as it is used in Order.

getOrder Source #

Arguments

:: (MonadResource m, MonadUnliftIO m, MonadThrow m) 
=> OrderId

Order ID.

-> UserAccessToken

User access token.

-> FacebookT anyAuth m Order 

Get an Order using its OrderId. The user access token is mandatory.

Friend list

data FriendListType Source #

Instances

Instances details
Enum FriendListType Source # 
Instance details

Defined in Facebook.Object.FriendList

Eq FriendListType Source # 
Instance details

Defined in Facebook.Object.FriendList

Ord FriendListType Source # 
Instance details

Defined in Facebook.Object.FriendList

Read FriendListType Source # 
Instance details

Defined in Facebook.Object.FriendList

Show FriendListType Source # 
Instance details

Defined in Facebook.Object.FriendList

ToJSON FriendListType Source # 
Instance details

Defined in Facebook.Object.FriendList

FromJSON FriendListType Source # 
Instance details

Defined in Facebook.Object.FriendList

getFriendListMembers Source #

Arguments

:: (MonadResource m, MonadUnliftIO m, MonadThrow m) 
=> Id

List ID.

-> [Argument]

Arguments to be passed to Facebook.

-> UserAccessToken

User access token.

-> FacebookT anyAuth m (Pager Friend) 

Get the members of a friend list.

Facebook's Graph API basic functionality

Simple types

(#=) :: SimpleType a => ByteString -> a -> Argument Source #

Create an Argument with a SimpleType. See the docs on createAction for an example.

class SimpleType a where Source #

Class for data types that may be represented as a Facebook simple type. (see https://developers.facebook.com/docs/opengraph/simpletypes/).

Instances

Instances details
SimpleType Bool Source #

Facebook's simple type Boolean.

Instance details

Defined in Facebook.Graph

SimpleType Double Source #

Facebook's simple type Float.

Instance details

Defined in Facebook.Graph

SimpleType Float Source #

Facebook's simple type Float with less precision than supported.

Instance details

Defined in Facebook.Graph

SimpleType Int Source #

Facebook's simple type Integer.

Instance details

Defined in Facebook.Graph

SimpleType Int8 Source #

Facebook's simple type Integer.

Instance details

Defined in Facebook.Graph

SimpleType Int16 Source #

Facebook's simple type Integer.

Instance details

Defined in Facebook.Graph

SimpleType Int32 Source #

Facebook's simple type Integer.

Instance details

Defined in Facebook.Graph

SimpleType Int64 Source #

Facebook's simple type Integer.

Instance details

Defined in Facebook.Graph

SimpleType Word Source #

Facebook's simple type Integer.

Instance details

Defined in Facebook.Graph

SimpleType Word8 Source #

Facebook's simple type Integer.

Instance details

Defined in Facebook.Graph

SimpleType Word16 Source #

Facebook's simple type Integer.

Instance details

Defined in Facebook.Graph

SimpleType Word32 Source #

Facebook's simple type Integer.

Instance details

Defined in Facebook.Graph

SimpleType Word64 Source #

Facebook's simple type Integer.

Instance details

Defined in Facebook.Graph

SimpleType ByteString Source #

Facebook's simple type String.

Instance details

Defined in Facebook.Graph

SimpleType UTCTime Source #

Facebook's simple type DateTime.

Instance details

Defined in Facebook.Graph

SimpleType Text Source #

Facebook's simple type String.

Instance details

Defined in Facebook.Graph

SimpleType ZonedTime Source #

Facebook's simple type DateTime.

Instance details

Defined in Facebook.Graph

SimpleType Day Source #

Facebook's simple type DateTime with only the date.

Instance details

Defined in Facebook.Graph

SimpleType Id Source #

An object's Id code.

Instance details

Defined in Facebook.Graph

SimpleType Permission Source #

Permission is a newtype of Text

Instance details

Defined in Facebook.Graph

SimpleType GeoCoordinates Source # 
Instance details

Defined in Facebook.Graph

SimpleType a => SimpleType [a] Source #

A comma-separated list of simple types. This definition doesn't work everywhere, just for a few combinations that Facebook uses (e.g. [Int]). Also, encoding a list of lists is the same as encoding the concatenation of all lists. In other words, this instance is here more for your convenience than to make sure your code is correct.

Instance details

Defined in Facebook.Graph

Methods

encodeFbParam :: [a] -> ByteString Source #

newtype FbUTCTime Source #

newtype for UTCTime that follows Facebook's conventions of JSON parsing.

  • As a string, while aeson expects a format of %FT%T%Q, Facebook gives time values formatted as %FT%T%z.
  • As a number, FbUTCTime accepts a number of seconds since the Unix epoch.

Constructors

FbUTCTime 

Fields

Complex types

data Place Source #

Information about a place. This is not a Graph Object, instead it's just a field of a Object. (Not to be confused with the Page object.)

Constructors

Place 

Fields

Instances

Instances details
Eq Place Source # 
Instance details

Defined in Facebook.Graph

Methods

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

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

Ord Place Source # 
Instance details

Defined in Facebook.Graph

Methods

compare :: Place -> Place -> Ordering #

(<) :: Place -> Place -> Bool #

(<=) :: Place -> Place -> Bool #

(>) :: Place -> Place -> Bool #

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

max :: Place -> Place -> Place #

min :: Place -> Place -> Place #

Read Place Source # 
Instance details

Defined in Facebook.Graph

Show Place Source # 
Instance details

Defined in Facebook.Graph

Methods

showsPrec :: Int -> Place -> ShowS #

show :: Place -> String #

showList :: [Place] -> ShowS #

FromJSON Place Source # 
Instance details

Defined in Facebook.Graph

data GeoCoordinates Source #

Geographical coordinates.

Constructors

GeoCoordinates 

Fields

data Tag Source #

A tag (i.e. "I'll tag you on my post").

Constructors

Tag 

Fields

Instances

Instances details
Eq Tag Source # 
Instance details

Defined in Facebook.Graph

Methods

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

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

Ord Tag Source # 
Instance details

Defined in Facebook.Graph

Methods

compare :: Tag -> Tag -> Ordering #

(<) :: Tag -> Tag -> Bool #

(<=) :: Tag -> Tag -> Bool #

(>) :: Tag -> Tag -> Bool #

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

max :: Tag -> Tag -> Tag #

min :: Tag -> Tag -> Tag #

Read Tag Source # 
Instance details

Defined in Facebook.Graph

Show Tag Source # 
Instance details

Defined in Facebook.Graph

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

FromJSON Tag Source # 
Instance details

Defined in Facebook.Graph

Pagination

data Pager a Source #

Many Graph API results are returned as a JSON object with the following structure:

{
  "data": [
    ...item 1...,
         :
    ...item n...
  ],
  "paging": {
    "previous": "http://...link to previous page...",
    "next":     "http://...link to next page..."
  }
}

Only the "data" field is required, the others may or may not appear.

A Pager a datatype encodes such result where each item has type a. You may use functions fetchNextPage and fetchPreviousPage to navigate through the results.

Constructors

Pager 

Instances

Instances details
Eq a => Eq (Pager a) Source # 
Instance details

Defined in Facebook.Pager

Methods

(==) :: Pager a -> Pager a -> Bool #

(/=) :: Pager a -> Pager a -> Bool #

Ord a => Ord (Pager a) Source # 
Instance details

Defined in Facebook.Pager

Methods

compare :: Pager a -> Pager a -> Ordering #

(<) :: Pager a -> Pager a -> Bool #

(<=) :: Pager a -> Pager a -> Bool #

(>) :: Pager a -> Pager a -> Bool #

(>=) :: Pager a -> Pager a -> Bool #

max :: Pager a -> Pager a -> Pager a #

min :: Pager a -> Pager a -> Pager a #

Read a => Read (Pager a) Source # 
Instance details

Defined in Facebook.Pager

Show a => Show (Pager a) Source # 
Instance details

Defined in Facebook.Pager

Methods

showsPrec :: Int -> Pager a -> ShowS #

show :: Pager a -> String #

showList :: [Pager a] -> ShowS #

FromJSON a => FromJSON (Pager a) Source # 
Instance details

Defined in Facebook.Pager

fetchNextPage :: (MonadResource m, FromJSON a, MonadThrow m, MonadUnliftIO m) => Pager a -> FacebookT anyAuth m (Maybe (Pager a)) Source #

Tries to fetch the next page of a Pager. Returns Nothing whenever the current Pager does not have a pagerNext.

fetchPreviousPage :: (MonadResource m, FromJSON a, MonadThrow m, MonadUnliftIO m) => Pager a -> FacebookT anyAuth m (Maybe (Pager a)) Source #

Tries to fetch the previous page of a Pager. Returns Nothing whenever the current Pager does not have a pagerPrevious.

fetchAllNextPages :: (Monad m, FromJSON a, MonadUnliftIO n, MonadThrow n) => Pager a -> FacebookT anyAuth m (ConduitT () a n ()) Source #

Tries to fetch all next pages and returns a Source with all results. The Source will include the results from this page as well. Previous pages will not be considered. Next pages will be fetched on-demand.

fetchAllPreviousPages :: (Monad m, FromJSON a, MonadUnliftIO n, MonadThrow n) => Pager a -> FacebookT anyAuth m (ConduitT () a n ()) Source #

Tries to fetch all previous pages and returns a Source with all results. The Source will include the results from this page as well. Next pages will not be considered. Previous pages will be fetched on-demand.

Real-time update notifications

Subscriptions

modifySubscription Source #

Arguments

:: (MonadResource m, MonadUnliftIO m, MonadThrow m) 
=> RealTimeUpdateObject

Type of objects whose subscription you and to add or modify.

-> [RealTimeUpdateField]

Fields that you are interested in receiving updates.

-> RealTimeUpdateUrl

Your callback URL.

-> RealTimeUpdateToken

A verification token.

-> AppAccessToken

Access token for your app.

-> FacebookT Auth m () 

Add or modify a subscription for real-time updates. If there were no previous subscriptions for the given RealTimeUpdateObject, then a new subscription is created. If there was any previous subscription for the given RealTimeUpdateObject, it's overriden by this one (even if the other subscription had a different callback URL).

listSubscriptions :: (MonadResource m, MonadUnliftIO m, MonadThrow m) => AppAccessToken -> FacebookT Auth m [RealTimeUpdateSubscription] Source #

List current real-time update subscriptions.

data RealTimeUpdateObject Source #

The type of objects that a real-time update refers to.

Instances

Instances details
Eq RealTimeUpdateObject Source # 
Instance details

Defined in Facebook.RealTime

Ord RealTimeUpdateObject Source # 
Instance details

Defined in Facebook.RealTime

Show RealTimeUpdateObject Source # 
Instance details

Defined in Facebook.RealTime

ToJSON RealTimeUpdateObject Source # 
Instance details

Defined in Facebook.RealTime

FromJSON RealTimeUpdateObject Source # 
Instance details

Defined in Facebook.RealTime

type RealTimeUpdateField = ByteString Source #

A field of a RealTimeUpdateObject that you would like to receive notifications when changed.

type RealTimeUpdateUrl = Text Source #

The URL on your server that will receive the real-time updates. Please refer to Facebook's documentation in order to see what this URL needs to implement.

type RealTimeUpdateToken = ByteString Source #

A token that is sent back by Facebook's servers to your server in order to verify that you really were trying to modify your subscription.

data RealTimeUpdateSubscription Source #

Information returned by Facebook about a real-time update notification subscription.

Notifications

verifyRealTimeUpdateNotifications Source #

Arguments

:: (Monad m, MonadIO m) 
=> ByteString

X-Hub-Signature HTTP header's value.

-> ByteString

Request body with JSON-encoded notifications.

-> FacebookT Auth m (Maybe ByteString) 

Verifi(es the input's authenticity (i.e. it comes from, MonadIO m) Facebook) and integrity by calculating its HMAC-SHA1 (using your application secret as the key) and verifying that it matches the value from the HTTP request's X-Hub-Signature header's value. If it's not valid, Nothing is returned, otherwise Just data is returned where data is the original data.

getRealTimeUpdateNotifications Source #

Arguments

:: (Monad m, FromJSON a, MonadIO m) 
=> ByteString

X-Hub-Signature HTTP header's value.

-> ByteString

Request body with JSON-encoded notifications.

-> FacebookT Auth m (Maybe (RealTimeUpdateNotification a)) 

Same as verifyRealTimeUpdateNotifications but also parses the response as JSON. Returns Nothing if either the signature is invalid or the data can't be parsed (use verifyRealTimeUpdateNotifications if you need to distinguish between these two error conditions).

data RealTimeUpdateNotification a Source #

When data changes and there's a valid subscription, Facebook will POST to your RealTimeUpdateUrl with a JSON-encoded object containing the notifications. A 'RealTimeUpdateNotification a' represents such object where a is type of the entries (e.g., RealTimeUpdateNotificationUserEntry).

If you have a single RealTimeUpdateUrl for different kinds of notifications, you may parse a RealTimeUpdateNotification Value and then manually parse the Value depending on the value of rtunObject.

We recommend using getRealTimeUpdateNotifications.

Instances

Instances details
Eq a => Eq (RealTimeUpdateNotification a) Source # 
Instance details

Defined in Facebook.RealTime

Ord a => Ord (RealTimeUpdateNotification a) Source # 
Instance details

Defined in Facebook.RealTime

Show a => Show (RealTimeUpdateNotification a) Source # 
Instance details

Defined in Facebook.RealTime

FromJSON a => FromJSON (RealTimeUpdateNotification a) Source # 
Instance details

Defined in Facebook.RealTime

data RealTimeUpdateNotificationUserEntry Source #

A notification for the UserRTUO object.

Instances

Instances details
Eq RealTimeUpdateNotificationUserEntry Source # 
Instance details

Defined in Facebook.RealTime

Ord RealTimeUpdateNotificationUserEntry Source # 
Instance details

Defined in Facebook.RealTime

Show RealTimeUpdateNotificationUserEntry Source # 
Instance details

Defined in Facebook.RealTime

FromJSON RealTimeUpdateNotificationUserEntry Source # 
Instance details

Defined in Facebook.RealTime

FQL

fqlQuery Source #

Arguments

:: (MonadResource m, MonadUnliftIO m, MonadThrow m, FromJSON a) 
=> Text

FQL Query

-> Maybe (AccessToken anyKind)

Optional access token

-> FacebookT anyAuth m (Pager a) 

Query the Facebook Graph using FQL.

newtype FQLTime Source #

Deprecated: Deprecated since fb 0.14.7, please use FbUTCTime instead.

newtype wrapper around UTCTime that is able to parse FQL's time representation as seconds since the Unix epoch.

Constructors

FQLTime

Deprecated: Deprecated since fb 0.14.7, please use FbUTCTime instead.

Fields

Instances

Instances details
Eq FQLTime Source # 
Instance details

Defined in Facebook.FQL

Methods

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

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

Ord FQLTime Source # 
Instance details

Defined in Facebook.FQL

Show FQLTime Source # 
Instance details

Defined in Facebook.FQL

FromJSON FQLTime Source # 
Instance details

Defined in Facebook.FQL

newtype FQLList a Source #

newtype wrapper around lists that works around FQL's strange lists.

For example, if you fetch the tagged_uids field from location_post, you'll find that Facebook's FQL represents an empty list of tagged UIDs as plain JSON array ([]). However, it represents a singleton list as an object {"1234": 1234} instead of the much more correct [1234].

On the other hand, not all FQL arrays are represented in this bogus manner. Also, some so-called arrays by FQL's documentation are actually objects, see FQLObject.

Constructors

FQLList 

Fields

Instances

Instances details
Eq a => Eq (FQLList a) Source # 
Instance details

Defined in Facebook.FQL

Methods

(==) :: FQLList a -> FQLList a -> Bool #

(/=) :: FQLList a -> FQLList a -> Bool #

Ord a => Ord (FQLList a) Source # 
Instance details

Defined in Facebook.FQL

Methods

compare :: FQLList a -> FQLList a -> Ordering #

(<) :: FQLList a -> FQLList a -> Bool #

(<=) :: FQLList a -> FQLList a -> Bool #

(>) :: FQLList a -> FQLList a -> Bool #

(>=) :: FQLList a -> FQLList a -> Bool #

max :: FQLList a -> FQLList a -> FQLList a #

min :: FQLList a -> FQLList a -> FQLList a #

Show a => Show (FQLList a) Source # 
Instance details

Defined in Facebook.FQL

Methods

showsPrec :: Int -> FQLList a -> ShowS #

show :: FQLList a -> String #

showList :: [FQLList a] -> ShowS #

FromJSON a => FromJSON (FQLList a) Source # 
Instance details

Defined in Facebook.FQL

newtype FQLObject a Source #

newtype wrapper around any object that works around FQL's strange objects.

For example, if you fetch the app_data field from stream, you'll find that empty objects are actually represented as empty lists [] instead of a proper empty object {}. Also note that FQL's documentation says that app_data is an array, which it clear is not. See also FQLList.

Constructors

FQLObject 

Fields

Instances

Instances details
Eq a => Eq (FQLObject a) Source # 
Instance details

Defined in Facebook.FQL

Methods

(==) :: FQLObject a -> FQLObject a -> Bool #

(/=) :: FQLObject a -> FQLObject a -> Bool #

Ord a => Ord (FQLObject a) Source # 
Instance details

Defined in Facebook.FQL

Show a => Show (FQLObject a) Source # 
Instance details

Defined in Facebook.FQL

FromJSON a => FromJSON (FQLObject a) Source # 
Instance details

Defined in Facebook.FQL

Test User API

getTestUsers Source #

Arguments

:: (MonadResource m, MonadUnliftIO m, MonadThrow m, MonadIO m) 
=> AppAccessToken

Access token for your app.

-> FacebookT Auth m (Pager TestUser) 

Get a list of test users.

removeTestUser Source #

Arguments

:: (MonadResource m, MonadUnliftIO m, MonadThrow m) 
=> TestUser

The TestUser to be removed.

-> AppAccessToken

Access token for your app (ignored since fb 0.14.7).

-> FacebookT Auth m Bool 

Remove an existing test user.

createTestUser Source #

Arguments

:: (MonadResource m, MonadUnliftIO m, MonadThrow m, MonadIO m) 
=> CreateTestUser

How the test user should be created.

-> AppAccessToken

Access token for your app.

-> FacebookT Auth m TestUser 

makeFriendConn :: (MonadResource m, MonadUnliftIO m, MonadThrow m) => TestUser -> TestUser -> FacebookT Auth m () Source #

Make a friend connection between two test users.

This is how Facebook's API work: two calls must be made. The first call has the format: "/userA_id/friends/userB_id" with the access token of user A as query parameter. The second call has the format: "/userB_id/friends/userA_id" with the access token of user B as query parameter. The first call creates a friend request and the second call accepts the friend request.

incompleteTestUserAccessToken :: TestUser -> Maybe UserAccessToken Source #

Create an UserAccessToken from a TestUser. It's incomplete because it will not have the right expiration time.

data CreateTestUser Source #

Data type used to hold information of a new test user. This type also accepts a Data.Default value.

Instances

Instances details
Default CreateTestUser Source #

Default instance for CreateTestUser.

Instance details

Defined in Facebook.TestUsers

Methods

def :: CreateTestUser #

data CreateTestUserInstalled Source #

Specify if the app is to be installed on the new test user. If it is, then you must tell what permissions should be given.

Constructors

CreateTestUserNotInstalled 
CreateTestUserInstalled 
CreateTestUserFbDefault

Uses Facebook's default. It seems that this is equivalent to

Instances

Instances details
Default CreateTestUserInstalled Source #

Default instance for CreateTestUserInstalled.

Instance details

Defined in Facebook.TestUsers

Raw access to the Graph API

getObject Source #

Arguments

:: (MonadResource m, MonadUnliftIO m, MonadThrow m, FromJSON a) 
=> Text

Path (should begin with a slash /)

-> [Argument]

Arguments to be passed to Facebook

-> Maybe (AccessToken anyKind)

Optional access token

-> FacebookT anyAuth m a 

Make a raw GET request to Facebook's Graph API.

postObject Source #

Arguments

:: (MonadResource m, MonadUnliftIO m, MonadThrow m, FromJSON a) 
=> Text

Path (should begin with a slash /)

-> [Argument]

Arguments to be passed to Facebook

-> AccessToken anyKind

Access token

-> FacebookT Auth m a 

Make a raw POST request to Facebook's Graph API.

deleteObject Source #

Arguments

:: (MonadResource m, MonadUnliftIO m, MonadThrow m, FromJSON a) 
=> Text

Path (should begin with a slash /)

-> [Argument]

Arguments to be passed to Facebook

-> AccessToken anyKind

Access token

-> FacebookT Auth m a 

Make a raw DELETE request to Facebook's Graph API.

searchObjects Source #

Arguments

:: (MonadResource m, MonadUnliftIO m, MonadThrow m, FromJSON a) 
=> Text

A Facebook object type to search for

-> Text

The keyword to search for

-> [Argument]

Additional arguments to pass

-> Maybe UserAccessToken

Optional access token

-> FacebookT anyAuth m (Pager a) 

Make a raw GET request to the /search endpoint of Facebook’s Graph API. Returns a raw JSON Value.

newtype Id Source #

The identification code of an object.

Constructors

Id 

Fields

Instances

Instances details
Eq Id Source # 
Instance details

Defined in Facebook.Types

Methods

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

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

Ord Id Source # 
Instance details

Defined in Facebook.Types

Methods

compare :: Id -> Id -> Ordering #

(<) :: Id -> Id -> Bool #

(<=) :: Id -> Id -> Bool #

(>) :: Id -> Id -> Bool #

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

max :: Id -> Id -> Id #

min :: Id -> Id -> Id #

Read Id Source # 
Instance details

Defined in Facebook.Types

Show Id Source # 
Instance details

Defined in Facebook.Types

Methods

showsPrec :: Int -> Id -> ShowS #

show :: Id -> String #

showList :: [Id] -> ShowS #

IsString Id Source # 
Instance details

Defined in Facebook.Types

Methods

fromString :: String -> Id #

ToJSON Id Source # 
Instance details

Defined in Facebook.Types

FromJSON Id Source # 
Instance details

Defined in Facebook.Types

SimpleType Id Source #

An object's Id code.

Instance details

Defined in Facebook.Graph

type Argument = (ByteString, ByteString) Source #

An argument given to an API call.

Exceptions

data FacebookException Source #

An exception that may be thrown by functions on this package. Includes any information provided by Facebook.

Constructors

FacebookException

An exception coming from Facebook.

Fields

FbLibraryException

An exception coming from the fb package's code.

Fields

Instances

Instances details
Eq FacebookException Source # 
Instance details

Defined in Facebook.Types

Ord FacebookException Source # 
Instance details

Defined in Facebook.Types

Read FacebookException Source # 
Instance details

Defined in Facebook.Types

Show FacebookException Source # 
Instance details

Defined in Facebook.Types

FromJSON FacebookException Source # 
Instance details

Defined in Facebook.Types

Exception FacebookException Source # 
Instance details

Defined in Facebook.Types

Internal functions

unPermission :: Permission -> Text Source #

Retrieves the Text back from a Permission. Most of the time you won't need to use this function, but you may need it if you're a library author.