| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Contents
Synopsis
- data FacebookT auth m a
- runFacebookT :: MonadIO m => Credentials -> Manager -> FacebookT Auth m a -> m a
- runNoAuthFacebookT :: MonadIO m => Manager -> FacebookT NoAuth m a -> m a
- mapFacebookT :: (m a -> n b) -> FacebookT anyAuth m a -> FacebookT anyAuth n b
- beta_runFacebookT :: MonadIO m => Credentials -> Manager -> FacebookT Auth m a -> m a
- beta_runNoAuthFacebookT :: MonadIO m => Manager -> FacebookT NoAuth m a -> m a
- data Auth
- data NoAuth
- data Credentials = Credentials {}
- data AccessToken kind where
- type UserAccessToken = AccessToken UserKind
- type AppAccessToken = AccessToken AppKind
- type AccessTokenData = Text
- type ApiVersion = Text
- hasExpired :: (Functor m, MonadIO m) => AccessToken anyKind -> m Bool
- isValid :: (MonadResource m, MonadUnliftIO m) => AccessToken anyKind -> FacebookT anyAuth m Bool
- setApiVersion :: MonadIO m => ApiVersion -> FacebookT anyAuth m ()
- getApiVersion :: MonadIO m => FacebookT anyAuth m ApiVersion
- data AppKind
- getAppAccessToken :: (MonadResource m, MonadUnliftIO m, MonadThrow m, MonadIO m) => FacebookT Auth m AppAccessToken
- data UserKind
- type RedirectUrl = Text
- data Permission
- getUserAccessTokenStep1 :: (Monad m, MonadIO m) => RedirectUrl -> [Permission] -> FacebookT Auth m Text
- getUserAccessTokenStep2 :: (MonadResource m, MonadUnliftIO m, MonadThrow m, MonadIO m) => RedirectUrl -> [Argument] -> FacebookT Auth m UserAccessToken
- getUserLogoutUrl :: Monad m => UserAccessToken -> RedirectUrl -> FacebookT Auth m Text
- extendUserAccessToken :: (MonadResource m, MonadUnliftIO m, MonadThrow m, MonadIO m) => UserAccessToken -> FacebookT Auth m (Either FacebookException UserAccessToken)
- debugToken :: (MonadResource m, MonadUnliftIO m, MonadThrow m) => AppAccessToken -> AccessTokenData -> FacebookT Auth m DebugToken
- data DebugToken = DebugToken {
- dtAppId :: Maybe Text
- dtAppName :: Maybe Text
- dtExpiresAt :: Maybe UTCTime
- dtIsValid :: Maybe Bool
- dtIssuedAt :: Maybe UTCTime
- dtScopes :: Maybe [Permission]
- dtUserId :: Maybe Id
- dtAccessToken :: Maybe UserAccessToken
- parseSignedRequest :: (FromJSON a, Monad m, MonadIO m) => ByteString -> FacebookT Auth m (Maybe a)
- addAppSecretProof :: Credentials -> Maybe (AccessToken anykind) -> SimpleQuery -> SimpleQuery
- makeAppSecretProof :: Credentials -> Maybe (AccessToken anyKind) -> SimpleQuery
- data User = User {}
- type UserId = Id
- data Gender
- getUser :: (MonadResource m, MonadUnliftIO m, MonadThrow m) => UserId -> [Argument] -> Maybe UserAccessToken -> FacebookT anyAuth m User
- searchUsers :: (MonadResource m, MonadUnliftIO m, MonadThrow m) => Text -> [Argument] -> Maybe UserAccessToken -> FacebookT anyAuth m (Pager User)
- getUserCheckins :: (MonadResource m, MonadUnliftIO m, MonadThrow m) => UserId -> [Argument] -> UserAccessToken -> FacebookT anyAuth m (Pager Checkin)
- data Friend = Friend {
- friendId :: UserId
- friendName :: Text
- getUserFriends :: (MonadResource m, MonadUnliftIO m, MonadThrow m) => UserId -> [Argument] -> UserAccessToken -> FacebookT anyAuth m (Pager Friend)
- getUserFriendLists :: (MonadResource m, MonadUnliftIO m, MonadThrow m) => UserId -> [Argument] -> UserAccessToken -> FacebookT anyAuth m (Pager FriendList)
- data Page = Page {
- pageId :: Id
- pageName :: Maybe Text
- pageLink :: Maybe Text
- pageCategory :: Maybe Text
- pageIsPublished :: Maybe Bool
- pageCanPost :: Maybe Bool
- pageLikes :: Maybe Integer
- pageLocation :: Maybe Location
- pagePhone :: Maybe Text
- pageCheckins :: Maybe Integer
- pagePicture :: Maybe Text
- pageWebsite :: Maybe Text
- pageTalkingAboutCount :: Maybe Integer
- getPage :: (MonadResource m, MonadUnliftIO m, MonadThrow m) => Id -> [Argument] -> Maybe UserAccessToken -> FacebookT anyAuth m Page
- getPage_ :: (MonadResource m, MonadUnliftIO m, MonadThrow m) => Id -> [Argument] -> Maybe AppAccessToken -> FacebookT anyAuth m Page
- searchPages :: (MonadResource m, MonadUnliftIO m, MonadThrow m) => Text -> [Argument] -> Maybe UserAccessToken -> FacebookT anyAuth m (Pager Page)
- data Action
- createAction :: (MonadResource m, MonadUnliftIO m, MonadThrow m, MonadIO m) => Action -> [Argument] -> Maybe AppAccessToken -> UserAccessToken -> FacebookT Auth m Id
- data Checkin = Checkin {}
- data CheckinFrom = CheckinFrom {}
- getCheckin :: (MonadResource m, MonadUnliftIO m, MonadThrow m) => Id -> [Argument] -> Maybe UserAccessToken -> FacebookT anyAuth m Checkin
- createCheckin :: (MonadResource m, MonadUnliftIO m, MonadThrow m) => Id -> GeoCoordinates -> [Argument] -> UserAccessToken -> FacebookT Auth m Id
- data Order = Order {}
- type OrderId = Id
- data OrderApplication
- data OrderStatus
- getOrder :: (MonadResource m, MonadUnliftIO m, MonadThrow m) => OrderId -> UserAccessToken -> FacebookT anyAuth m Order
- data FriendList = FriendList {}
- data FriendListType
- getFriendListMembers :: (MonadResource m, MonadUnliftIO m, MonadThrow m) => Id -> [Argument] -> UserAccessToken -> FacebookT anyAuth m (Pager Friend)
- (#=) :: SimpleType a => ByteString -> a -> Argument
- class SimpleType a where
- encodeFbParam :: a -> ByteString
- newtype FbUTCTime = FbUTCTime {}
- data Place = Place {}
- data Location = Location {}
- data GeoCoordinates = GeoCoordinates {}
- data Tag = Tag {}
- data Pager a = Pager {}
- fetchNextPage :: (MonadResource m, FromJSON a, MonadThrow m, MonadUnliftIO m) => Pager a -> FacebookT anyAuth m (Maybe (Pager a))
- fetchPreviousPage :: (MonadResource m, FromJSON a, MonadThrow m, MonadUnliftIO m) => Pager a -> FacebookT anyAuth m (Maybe (Pager a))
- fetchAllNextPages :: (Monad m, FromJSON a, MonadUnliftIO n, MonadThrow n) => Pager a -> FacebookT anyAuth m (ConduitT () a n ())
- fetchAllPreviousPages :: (Monad m, FromJSON a, MonadUnliftIO n, MonadThrow n) => Pager a -> FacebookT anyAuth m (ConduitT () a n ())
- modifySubscription :: (MonadResource m, MonadUnliftIO m, MonadThrow m) => RealTimeUpdateObject -> [RealTimeUpdateField] -> RealTimeUpdateUrl -> RealTimeUpdateToken -> AppAccessToken -> FacebookT Auth m ()
- listSubscriptions :: (MonadResource m, MonadUnliftIO m, MonadThrow m) => AppAccessToken -> FacebookT Auth m [RealTimeUpdateSubscription]
- data RealTimeUpdateObject
- type RealTimeUpdateField = ByteString
- type RealTimeUpdateUrl = Text
- type RealTimeUpdateToken = ByteString
- data RealTimeUpdateSubscription = RealTimeUpdateSubscription {}
- verifyRealTimeUpdateNotifications :: (Monad m, MonadIO m) => ByteString -> ByteString -> FacebookT Auth m (Maybe ByteString)
- getRealTimeUpdateNotifications :: (Monad m, FromJSON a, MonadIO m) => ByteString -> ByteString -> FacebookT Auth m (Maybe (RealTimeUpdateNotification a))
- data RealTimeUpdateNotification a = RealTimeUpdateNotification {
- rtunObject :: RealTimeUpdateObject
- rtunEntries :: [a]
- data RealTimeUpdateNotificationUserEntry = RealTimeUpdateNotificationUserEntry {}
- fqlQuery :: (MonadResource m, MonadUnliftIO m, MonadThrow m, FromJSON a) => Text -> Maybe (AccessToken anyKind) -> FacebookT anyAuth m (Pager a)
- newtype FQLTime = FQLTime {}
- newtype FQLList a = FQLList {
- unFQLList :: [a]
- newtype FQLObject a = FQLObject {
- unFQLObject :: a
- getTestUsers :: (MonadResource m, MonadUnliftIO m, MonadThrow m, MonadIO m) => AppAccessToken -> FacebookT Auth m (Pager TestUser)
- disassociateTestuser :: (MonadUnliftIO m, MonadThrow m, MonadResource m, MonadIO m) => TestUser -> AppAccessToken -> FacebookT Auth m Bool
- removeTestUser :: (MonadResource m, MonadUnliftIO m, MonadThrow m) => TestUser -> AppAccessToken -> FacebookT Auth m Bool
- createTestUser :: (MonadResource m, MonadUnliftIO m, MonadThrow m, MonadIO m) => CreateTestUser -> AppAccessToken -> FacebookT Auth m TestUser
- makeFriendConn :: (MonadResource m, MonadUnliftIO m, MonadThrow m) => TestUser -> TestUser -> FacebookT Auth m ()
- incompleteTestUserAccessToken :: TestUser -> Maybe UserAccessToken
- data TestUser = TestUser {}
- data CreateTestUser = CreateTestUser {}
- data CreateTestUserInstalled
- getObject :: (MonadResource m, MonadUnliftIO m, MonadThrow m, FromJSON a) => Text -> [Argument] -> Maybe (AccessToken anyKind) -> FacebookT anyAuth m a
- postObject :: (MonadResource m, MonadUnliftIO m, MonadThrow m, FromJSON a) => Text -> [Argument] -> AccessToken anyKind -> FacebookT Auth m a
- deleteObject :: (MonadResource m, MonadUnliftIO m, MonadThrow m, FromJSON a) => Text -> [Argument] -> AccessToken anyKind -> FacebookT Auth m a
- searchObjects :: (MonadResource m, MonadUnliftIO m, MonadThrow m, FromJSON a) => Text -> Text -> [Argument] -> Maybe UserAccessToken -> FacebookT anyAuth m (Pager a)
- newtype Id = Id {}
- type Argument = (ByteString, ByteString)
- data FacebookException
- = FacebookException {
- fbeType :: Text
- fbeMessage :: Text
- | FbLibraryException {
- fbeMessage :: Text
- = FacebookException {
- unPermission :: Permission -> Text
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
Arguments
| :: MonadIO m | |
| => Credentials | Your app's credentials. |
| -> Manager | Connection manager (see |
| -> FacebookT Auth m a | |
| -> m a |
Run a computation in the FacebookT monad transformer with
your credentials.
Arguments
| :: MonadIO m | |
| => Manager | Connection manager (see |
| -> 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.
beta_runFacebookT :: MonadIO m => Credentials -> Manager -> FacebookT Auth m a -> m a Source #
Same as runFacebookT, but uses Facebook's beta tier (see
https://developers.facebook.com/support/beta-tier/).
beta_runNoAuthFacebookT :: MonadIO m => Manager -> FacebookT NoAuth m a -> m a Source #
Same as runNoAuthFacebookT, but uses Facebook's beta tier
(see https://developers.facebook.com/support/beta-tier/).
Phantom type stating that you have provided your
Credentials and thus have access to the whole API.
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 | |
Instances
| Eq Credentials Source # | |
Defined in Facebook.Types | |
| Ord Credentials Source # | |
Defined in Facebook.Types Methods compare :: Credentials -> Credentials -> Ordering # (<) :: Credentials -> Credentials -> Bool # (<=) :: Credentials -> Credentials -> Bool # (>) :: Credentials -> Credentials -> Bool # (>=) :: Credentials -> Credentials -> Bool # max :: Credentials -> Credentials -> Credentials # min :: Credentials -> Credentials -> Credentials # | |
| Read Credentials Source # | |
Defined in Facebook.Types Methods readsPrec :: Int -> ReadS Credentials # readList :: ReadS [Credentials] # readPrec :: ReadPrec Credentials # readListPrec :: ReadPrec [Credentials] # | |
| Show Credentials Source # | |
Defined in Facebook.Types Methods showsPrec :: Int -> Credentials -> ShowS # show :: Credentials -> String # showList :: [Credentials] -> ShowS # | |
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.
Constructors
| UserAccessToken :: UserId -> AccessTokenData -> UTCTime -> AccessToken UserKind | |
| AppAccessToken :: AccessTokenData -> AccessToken AppKind |
Instances
| Eq (AccessToken kind) Source # | |
Defined in Facebook.Types Methods (==) :: AccessToken kind -> AccessToken kind -> Bool # (/=) :: AccessToken kind -> AccessToken kind -> Bool # | |
| Ord (AccessToken kind) Source # | |
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 # | |
Defined in Facebook.Types Methods showsPrec :: Int -> AccessToken kind -> ShowS # show :: AccessToken kind -> String # showList :: [AccessToken kind] -> ShowS # | |
| ToJSON (AccessToken kind) Source # | Synonym for Since 0.14.9. Not a Facebook JSON format, but a custom |
Defined in Facebook.Types Methods toJSON :: AccessToken kind -> Value # toEncoding :: AccessToken kind -> Encoding # toJSONList :: [AccessToken kind] -> Value # toEncodingList :: [AccessToken kind] -> Encoding # | |
| ParseAccessToken kind => FromJSON (AccessToken kind) Source # | Since 0.14.9. Parses the format that |
Defined in Facebook.Types Methods parseJSON :: Value -> Parser (AccessToken kind) # parseJSONList :: Value -> Parser [AccessToken kind] # | |
type UserAccessToken = AccessToken UserKind Source #
Type synonym for .AccessToken UserKind
type AppAccessToken = AccessToken AppKind Source #
Type synonym for .AccessToken AppKind
type AccessTokenData = Text Source #
The access token data that is passed to Facebook's API calls.
type ApiVersion = Text Source #
Graph API version. See: https://developers.facebook.com/docs/graph-api/changelog
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
Phantom type used mark an AccessToken as an app access
token.
getAppAccessToken :: (MonadResource m, MonadUnliftIO m, MonadThrow m, MonadIO m) => FacebookT Auth m AppAccessToken Source #
Get an app access token from Facebook using your credentials. Ref: https://developers.facebook.com/docs/facebook-login/manually-build-a-login-flow
User access token
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
| Eq Permission Source # | |
Defined in Facebook.Auth | |
| Ord Permission Source # | |
Defined in Facebook.Auth Methods compare :: Permission -> Permission -> Ordering # (<) :: Permission -> Permission -> Bool # (<=) :: Permission -> Permission -> Bool # (>) :: Permission -> Permission -> Bool # (>=) :: Permission -> Permission -> Bool # max :: Permission -> Permission -> Permission # min :: Permission -> Permission -> Permission # | |
| Show Permission Source # | |
Defined in Facebook.Auth Methods showsPrec :: Int -> Permission -> ShowS # show :: Permission -> String # showList :: [Permission] -> ShowS # | |
| IsString Permission Source # | |
Defined in Facebook.Auth Methods fromString :: String -> Permission # | |
| SimpleType Permission Source # |
|
Defined in Facebook.Graph Methods encodeFbParam :: Permission -> ByteString Source # | |
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 |
| -> [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 .AccessToken
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
|
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.
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).
Constructors
| DebugToken | |
Fields
| |
Instances
| Eq DebugToken Source # | |
Defined in Facebook.Auth | |
| Ord DebugToken Source # | |
Defined in Facebook.Auth Methods compare :: DebugToken -> DebugToken -> Ordering # (<) :: DebugToken -> DebugToken -> Bool # (<=) :: DebugToken -> DebugToken -> Bool # (>) :: DebugToken -> DebugToken -> Bool # (>=) :: DebugToken -> DebugToken -> Bool # max :: DebugToken -> DebugToken -> DebugToken # min :: DebugToken -> DebugToken -> DebugToken # | |
| Show DebugToken Source # | |
Defined in Facebook.Auth Methods showsPrec :: Int -> DebugToken -> ShowS # show :: DebugToken -> String # showList :: [DebugToken] -> ShowS # | |
| FromJSON DebugToken Source # | Note: this instance always sets |
Defined in Facebook.Auth | |
Signed requests
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.
addAppSecretProof :: Credentials -> Maybe (AccessToken anykind) -> SimpleQuery -> SimpleQuery 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
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.
Constructors
| User | |
Fields
| |
An user's gender.
Arguments
| :: (MonadResource m, MonadUnliftIO m, MonadThrow m) | |
| => UserId | User ID or |
| -> [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.
Arguments
| :: (MonadResource m, MonadUnliftIO m, MonadThrow m) | |
| => UserId | User ID or |
| -> [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.
A friend connection of a User.
Constructors
| Friend | |
Fields
| |
Arguments
| :: (MonadResource m, MonadUnliftIO m, MonadThrow m) | |
| => UserId | User ID or |
| -> [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.
Arguments
| :: (MonadResource m, MonadUnliftIO m, MonadThrow m) | |
| => UserId | User ID or |
| -> [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
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.
Constructors
| Page | |
Fields
| |
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.
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.
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
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" [...] tokenArguments
| :: (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 ]
tokenCheckins
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.
Constructors
| Checkin | |
Fields
| |
data CheckinFrom Source #
Information about the user who made the check-in.
Constructors
| CheckinFrom | |
Fields | |
Instances
| Eq CheckinFrom Source # | |
Defined in Facebook.Object.Checkin | |
| Ord CheckinFrom Source # | |
Defined in Facebook.Object.Checkin Methods compare :: CheckinFrom -> CheckinFrom -> Ordering # (<) :: CheckinFrom -> CheckinFrom -> Bool # (<=) :: CheckinFrom -> CheckinFrom -> Bool # (>) :: CheckinFrom -> CheckinFrom -> Bool # (>=) :: CheckinFrom -> CheckinFrom -> Bool # max :: CheckinFrom -> CheckinFrom -> CheckinFrom # min :: CheckinFrom -> CheckinFrom -> CheckinFrom # | |
| Read CheckinFrom Source # | |
Defined in Facebook.Object.Checkin Methods readsPrec :: Int -> ReadS CheckinFrom # readList :: ReadS [CheckinFrom] # readPrec :: ReadPrec CheckinFrom # readListPrec :: ReadPrec [CheckinFrom] # | |
| Show CheckinFrom Source # | |
Defined in Facebook.Object.Checkin Methods showsPrec :: Int -> CheckinFrom -> ShowS # show :: CheckinFrom -> String # showList :: [CheckinFrom] -> ShowS # | |
| FromJSON CheckinFrom Source # | |
Defined in Facebook.Object.Checkin | |
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.
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
A Facebook Order oject.
Constructors
| Order | |
Fields | |
data OrderApplication Source #
A trimmed down version of Facebook Application as it is used in Order.
Instances
| Show OrderApplication Source # | |
Defined in Facebook.Object.Order Methods showsPrec :: Int -> OrderApplication -> ShowS # show :: OrderApplication -> String # showList :: [OrderApplication] -> ShowS # | |
| FromJSON OrderApplication Source # | |
Defined in Facebook.Object.Order Methods parseJSON :: Value -> Parser OrderApplication # parseJSONList :: Value -> Parser [OrderApplication] # | |
data OrderStatus Source #
A Facebook Order status type.
Instances
| Enum OrderStatus Source # | |
Defined in Facebook.Object.Order Methods succ :: OrderStatus -> OrderStatus # pred :: OrderStatus -> OrderStatus # toEnum :: Int -> OrderStatus # fromEnum :: OrderStatus -> Int # enumFrom :: OrderStatus -> [OrderStatus] # enumFromThen :: OrderStatus -> OrderStatus -> [OrderStatus] # enumFromTo :: OrderStatus -> OrderStatus -> [OrderStatus] # enumFromThenTo :: OrderStatus -> OrderStatus -> OrderStatus -> [OrderStatus] # | |
| Eq OrderStatus Source # | |
Defined in Facebook.Object.Order | |
| Show OrderStatus Source # | |
Defined in Facebook.Object.Order Methods showsPrec :: Int -> OrderStatus -> ShowS # show :: OrderStatus -> String # showList :: [OrderStatus] -> ShowS # | |
| FromJSON OrderStatus Source # | |
Defined in Facebook.Object.Order | |
Arguments
| :: (MonadResource m, MonadUnliftIO m, MonadThrow m) | |
| => OrderId | Order ID. |
| -> UserAccessToken | User access token. |
| -> FacebookT anyAuth m Order |
Friend list
data FriendList Source #
A friend list for a User.
Constructors
| FriendList | |
Fields | |
Instances
| Eq FriendList Source # | |
Defined in Facebook.Object.FriendList | |
| Ord FriendList Source # | |
Defined in Facebook.Object.FriendList Methods compare :: FriendList -> FriendList -> Ordering # (<) :: FriendList -> FriendList -> Bool # (<=) :: FriendList -> FriendList -> Bool # (>) :: FriendList -> FriendList -> Bool # (>=) :: FriendList -> FriendList -> Bool # max :: FriendList -> FriendList -> FriendList # min :: FriendList -> FriendList -> FriendList # | |
| Read FriendList Source # | |
Defined in Facebook.Object.FriendList Methods readsPrec :: Int -> ReadS FriendList # readList :: ReadS [FriendList] # readPrec :: ReadPrec FriendList # readListPrec :: ReadPrec [FriendList] # | |
| Show FriendList Source # | |
Defined in Facebook.Object.FriendList Methods showsPrec :: Int -> FriendList -> ShowS # show :: FriendList -> String # showList :: [FriendList] -> ShowS # | |
| FromJSON FriendList Source # | |
Defined in Facebook.Object.FriendList | |
data FriendListType Source #
Constructors
| CloseFriendsList | |
| AcquaintancesList | |
| RestrictedList | |
| UserCreatedList | |
| EducationList | |
| WorkList | |
| CurrentCityList | |
| FamilyList |
Instances
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/).
Methods
encodeFbParam :: a -> ByteString Source #
Instances
| SimpleType Bool Source # | Facebook's simple type |
Defined in Facebook.Graph Methods encodeFbParam :: Bool -> ByteString Source # | |
| SimpleType Double Source # | Facebook's simple type |
Defined in Facebook.Graph Methods encodeFbParam :: Double -> ByteString Source # | |
| SimpleType Float Source # | Facebook's simple type |
Defined in Facebook.Graph Methods encodeFbParam :: Float -> ByteString Source # | |
| SimpleType Int Source # | Facebook's simple type |
Defined in Facebook.Graph Methods encodeFbParam :: Int -> ByteString Source # | |
| SimpleType Int8 Source # | Facebook's simple type |
Defined in Facebook.Graph Methods encodeFbParam :: Int8 -> ByteString Source # | |
| SimpleType Int16 Source # | Facebook's simple type |
Defined in Facebook.Graph Methods encodeFbParam :: Int16 -> ByteString Source # | |
| SimpleType Int32 Source # | Facebook's simple type |
Defined in Facebook.Graph Methods encodeFbParam :: Int32 -> ByteString Source # | |
| SimpleType Int64 Source # | Facebook's simple type |
Defined in Facebook.Graph Methods encodeFbParam :: Int64 -> ByteString Source # | |
| SimpleType Word Source # | Facebook's simple type |
Defined in Facebook.Graph Methods encodeFbParam :: Word -> ByteString Source # | |
| SimpleType Word8 Source # | Facebook's simple type |
Defined in Facebook.Graph Methods encodeFbParam :: Word8 -> ByteString Source # | |
| SimpleType Word16 Source # | Facebook's simple type |
Defined in Facebook.Graph Methods encodeFbParam :: Word16 -> ByteString Source # | |
| SimpleType Word32 Source # | Facebook's simple type |
Defined in Facebook.Graph Methods encodeFbParam :: Word32 -> ByteString Source # | |
| SimpleType Word64 Source # | Facebook's simple type |
Defined in Facebook.Graph Methods encodeFbParam :: Word64 -> ByteString Source # | |
| SimpleType ByteString Source # | Facebook's simple type |
Defined in Facebook.Graph Methods encodeFbParam :: ByteString -> ByteString Source # | |
| SimpleType Text Source # | Facebook's simple type |
Defined in Facebook.Graph Methods encodeFbParam :: Text -> ByteString Source # | |
| SimpleType UTCTime Source # | Facebook's simple type |
Defined in Facebook.Graph Methods encodeFbParam :: UTCTime -> ByteString Source # | |
| SimpleType ZonedTime Source # | Facebook's simple type |
Defined in Facebook.Graph Methods encodeFbParam :: ZonedTime -> ByteString Source # | |
| SimpleType Day Source # | Facebook's simple type |
Defined in Facebook.Graph Methods encodeFbParam :: Day -> ByteString Source # | |
| SimpleType Id Source # | An object's |
Defined in Facebook.Graph Methods encodeFbParam :: Id -> ByteString Source # | |
| SimpleType Permission Source # |
|
Defined in Facebook.Graph Methods encodeFbParam :: Permission -> ByteString Source # | |
| SimpleType GeoCoordinates Source # | |
Defined in Facebook.Graph Methods | |
| 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. |
Defined in Facebook.Graph Methods encodeFbParam :: [a] -> ByteString Source # | |
newtype for UTCTime that follows Facebook's
conventions of JSON parsing.
- As a string, while
aesonexpects a format of%FT%T%Q, Facebook gives time values formatted as%FT%T%z. - As a number,
FbUTCTimeaccepts a number of seconds since the Unix epoch.
Constructors
| FbUTCTime | |
Fields | |
Instances
| Eq FbUTCTime Source # | |
| Ord FbUTCTime Source # | |
| Read FbUTCTime Source # | |
| Show FbUTCTime Source # | |
| FromJSON FbUTCTime Source # | |
Complex types
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 | |
A geographical location.
Constructors
| Location | |
Fields | |
data GeoCoordinates Source #
Geographical coordinates.
Constructors
| GeoCoordinates | |
Instances
A tag (i.e. "I'll tag you on my post").
Pagination
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.
fetchNextPage :: (MonadResource m, FromJSON a, MonadThrow m, MonadUnliftIO m) => Pager a -> FacebookT anyAuth m (Maybe (Pager a)) Source #
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 #
fetchAllPreviousPages :: (Monad m, FromJSON a, MonadUnliftIO n, MonadThrow n) => Pager a -> FacebookT anyAuth m (ConduitT () a n ()) Source #
Real-time update notifications
Subscriptions
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.
Constructors
| UserRTUO | |
| PermissionsRTUO | |
| PageRTUO | |
| ErrorsRTUO | |
| OtherRTUO Text |
Instances
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.
Constructors
| RealTimeUpdateSubscription | |
Fields | |
Instances
Notifications
verifyRealTimeUpdateNotifications Source #
Arguments
| :: (Monad m, MonadIO m) | |
| => ByteString |
|
| -> 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 |
|
| -> 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
and then manually parse the ValueValue depending on
the value of rtunObject.
We recommend using getRealTimeUpdateNotifications.
Constructors
| RealTimeUpdateNotification | |
Fields
| |
Instances
data RealTimeUpdateNotificationUserEntry Source #
A notification for the UserRTUO object.
Constructors
| RealTimeUpdateNotificationUserEntry | |
Fields | |
Instances
FQL
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.
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. |
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.
Instances
| Eq a => Eq (FQLList a) Source # | |
| Ord a => Ord (FQLList a) Source # | |
| Show a => Show (FQLList a) Source # | |
| FromJSON a => FromJSON (FQLList 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
| Eq a => Eq (FQLObject a) Source # | |
| Ord a => Ord (FQLObject a) Source # | |
Defined in Facebook.FQL | |
| Show a => Show (FQLObject a) Source # | |
| FromJSON a => FromJSON (FQLObject a) Source # | |
Test User API
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.
disassociateTestuser :: (MonadUnliftIO m, MonadThrow m, MonadResource m, MonadIO m) => TestUser -> AppAccessToken -> FacebookT Auth m Bool 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.
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 |
Create a new test user. Ref: https://developers.facebook.com/docs/graph-api/reference/v2.8/app/accounts/test-users#publish
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 AccessToken from a TestUser. It's incomplete
because it will not have the right expiration time.
A Facebook test user. Ref: https://developers.facebook.com/docs/graph-api/reference/v2.8/app/accounts/test-users
Constructors
| TestUser | |
Fields
| |
data CreateTestUser Source #
Data type used to hold information of a new test user. This type also accepts a Data.Default value.
Constructors
| CreateTestUser | |
Fields | |
Instances
| Default CreateTestUser Source # | Default instance for |
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 | |
Fields | |
| CreateTestUserFbDefault | Uses Facebook's default. It seems that this is equivalent to |
Instances
| Default CreateTestUserInstalled Source # | Default instance for |
Defined in Facebook.TestUsers Methods | |
Raw access to the Graph API
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.
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.
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.
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.
The identification code of an object.
Instances
| Eq Id Source # | |
| Ord Id Source # | |
| Read Id Source # | |
| Show Id Source # | |
| IsString Id Source # | |
Defined in Facebook.Types Methods fromString :: String -> Id # | |
| ToJSON Id Source # | |
Defined in Facebook.Types | |
| FromJSON Id Source # | |
| SimpleType Id Source # | An object's |
Defined in Facebook.Graph Methods encodeFbParam :: Id -> ByteString Source # | |
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 |
Fields
| |
Instances
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.