| Safe Haskell | None | 
|---|
Contents
- data FacebookT auth m a
- runFacebookT :: Credentials -> Manager -> FacebookT Auth m a -> m a
- runNoAuthFacebookT :: Manager -> FacebookT NoAuth m a -> m a
- beta_runFacebookT :: Credentials -> Manager -> FacebookT Auth m a -> m a
- beta_runNoAuthFacebookT :: 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 = Ascii
- hasExpired :: (Functor m, MonadIO m) => AccessToken anyKind -> m Bool
- isValid :: (MonadBaseControl IO m, MonadResource m) => AccessToken anyKind -> FacebookT anyAuth m Bool
- data AppKind
- getAppAccessToken :: (MonadResource m, MonadBaseControl IO m) => FacebookT Auth m AppAccessToken
- data UserKind
- type RedirectUrl = Text
- data Permission
- getUserAccessTokenStep1 :: Monad m => RedirectUrl -> [Permission] -> FacebookT Auth m Text
- getUserAccessTokenStep2 :: (MonadBaseControl IO m, MonadResource m) => RedirectUrl -> [Argument] -> FacebookT Auth m UserAccessToken
- getUserLogoutUrl :: Monad m => UserAccessToken -> RedirectUrl -> FacebookT Auth m Text
- extendUserAccessToken :: (MonadBaseControl IO m, MonadResource m) => UserAccessToken -> FacebookT Auth m (Either FacebookException UserAccessToken)
- parseSignedRequest :: (FromJSON a, Monad m) => ByteString -> FacebookT Auth m (Maybe a)
- data User = User {}
- type UserId = Ascii
- data Gender
- data UserLocation = UserLocation {}
- getUser :: (MonadResource m, MonadBaseControl IO m) => UserId -> [Argument] -> Maybe UserAccessToken -> FacebookT anyAuth m User
- createAction :: (MonadResource m, MonadBaseControl IO m) => Action -> [Argument] -> Maybe AppAccessToken -> UserAccessToken -> FacebookT Auth m Id
- data Action
- createCheckin :: (MonadResource m, MonadBaseControl IO m) => Id -> (Double, Double) -> [Argument] -> UserAccessToken -> FacebookT Auth m Id
- fqlQuery :: (MonadResource m, MonadBaseControl IO m, FromJSON a) => Text -> Maybe (AccessToken anyKind) -> FacebookT anyAuth m a
- newtype FQLResult a = FQLResult [a]
- (#=) :: SimpleType a => Ascii -> a -> Argument
- class  SimpleType a  where- encodeFbParam :: a -> ByteString
 
- getObject :: (MonadResource m, MonadBaseControl IO m, FromJSON a) => Ascii -> [Argument] -> Maybe (AccessToken anyKind) -> FacebookT anyAuth m a
- postObject :: (MonadResource m, MonadBaseControl IO m, FromJSON a) => Ascii -> [Argument] -> AccessToken anyKind -> FacebookT Auth m 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
| MonadBase b m => MonadBase b (FacebookT auth m) | |
| MonadBaseControl b m => MonadBaseControl b (FacebookT auth m) | |
| MonadTrans (FacebookT auth) | |
| MonadTransControl (FacebookT auth) | |
| Monad m => Monad (FacebookT auth m) | |
| Functor m => Functor (FacebookT auth m) | |
| MonadFix m => MonadFix (FacebookT auth m) | |
| MonadPlus m => MonadPlus (FacebookT auth m) | |
| Applicative m => Applicative (FacebookT auth m) | |
| Alternative m => Alternative (FacebookT auth m) | |
| MonadIO m => MonadIO (FacebookT auth m) | 
Arguments
| :: 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.
runNoAuthFacebookT :: Manager -> FacebookT NoAuth m a -> m aSource
Run a computation in the FacebookT monad without
 credentials.
beta_runFacebookT :: Credentials -> Manager -> FacebookT Auth m a -> m aSource
Same as runFacebookT, but uses Facebook's beta tier (see
 https://developers.facebook.com/support/beta-tier/).
beta_runNoAuthFacebookT :: Manager -> FacebookT NoAuth m a -> m aSource
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 | |
| Ord Credentials | |
| Read Credentials | |
| Show Credentials | |
| Typeable Credentials | |
| ToSimpleQuery Credentials | 
Access token
data AccessToken kind whereSource
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
| Typeable1 AccessToken | |
| Eq (AccessToken kind) | |
| Ord (AccessToken kind) | |
| Show (AccessToken kind) | |
| ToSimpleQuery (AccessToken anyKind) | 
type UserAccessToken = AccessToken UserKindSource
Type synonym for AccessToken UserKind
type AppAccessToken = AccessToken AppKindSource
Type synonym for AccessToken AppKind
type AccessTokenData = AsciiSource
The access token data that is passed to Facebook's API calls.
hasExpired :: (Functor m, MonadIO m) => AccessToken anyKind -> m BoolSource
True if the access token has expired, otherwise False.
isValid :: (MonadBaseControl IO m, MonadResource m) => AccessToken anyKind -> FacebookT anyAuth m BoolSource
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.
App access token
Phantom type used mark an AccessToken as an app access
 token.
getAppAccessToken :: (MonadResource m, MonadBaseControl IO m) => FacebookT Auth m AppAccessTokenSource
Get an app access token from Facebook using your credentials.
User access token
Phantom type used mark an AccessToken as an user access
 token.
type RedirectUrl = TextSource
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
getUserAccessTokenStep1 :: Monad m => RedirectUrl -> [Permission] -> FacebookT Auth m TextSource
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.
Arguments
| :: (MonadBaseControl IO m, MonadResource 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 UserAccessToken
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 :: (MonadBaseControl IO m, MonadResource 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.
Signed requests
Arguments
| :: (FromJSON a, Monad 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.
Facebook's Graph API Objects
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.
data UserLocation Source
An user's location.
Constructors
| UserLocation | |
| Fields 
 | |
Arguments
| :: (MonadResource m, MonadBaseControl IO 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.
Facebook's Open Graph API
Actions
Arguments
| :: (MonadResource m, MonadBaseControl IO 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
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 Ascii 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
Checkins
Arguments
| :: (MonadResource m, MonadBaseControl IO m) | |
| => Id | Place Id | 
| -> (Double, Double) | (Latitude, Longitude) | 
| -> [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.
FQL
Arguments
| :: (MonadResource m, MonadBaseControl IO m, FromJSON a) | |
| => Text | FQL Query | 
| -> Maybe (AccessToken anyKind) | Optional access token | 
| -> FacebookT anyAuth m a | 
Query the Facebook Graph using FQL.  You may want to use
 FQLResult when parsing the returned JSON.
Parses an FQL query result. FQL query results are always of the form
   { data: [ret1, ret2, ...] }
This newtype unwraps the array from the data field
 automatically for you, so you may write something like:
FQLResult [...] <- fqlQuery ...
Constructors
| FQLResult [a] | 
Helpers
(#=) :: SimpleType a => Ascii -> a -> ArgumentSource
Create an Argument with a SimpleType.  See the docs on
 createAction for an example.
class SimpleType a whereSource
Class for data types that may be represented as a Facebook simple type. (see https://developers.facebook.com/docs/opengraph/simpletypes/).
Methods
encodeFbParam :: a -> ByteStringSource
Instances
| SimpleType Bool | Facebook's simple type  | 
| SimpleType Double | Facebook's simple type  | 
| SimpleType Float | Facebook's simple type  | 
| SimpleType Int | Facebook's simple type  | 
| SimpleType Int8 | Facebook's simple type  | 
| SimpleType Int16 | Facebook's simple type  | 
| SimpleType Int32 | Facebook's simple type  | 
| SimpleType Word | Facebook's simple type  | 
| SimpleType Word8 | Facebook's simple type  | 
| SimpleType Word16 | Facebook's simple type  | 
| SimpleType Word32 | Facebook's simple type  | 
| SimpleType Text | Facebook's simple type  | 
| SimpleType UTCTime | Facebook's simple type  | 
| SimpleType ZonedTime | Facebook's simple type  | 
| SimpleType Day | Facebook's simple type  | 
| SimpleType Id | An object's  | 
| SimpleType a => SimpleType [a] | A comma-separated list of simple types.  This definition
 doesn't work everywhere, just for a few combinations that
 Facebook uses (e.g.  | 
Raw access to the Graph API
Arguments
| :: (MonadResource m, MonadBaseControl IO m, FromJSON a) | |
| => Ascii | 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.  Returns a
 raw JSON Value.
Arguments
| :: (MonadResource m, MonadBaseControl IO m, FromJSON a) | |
| => Ascii | 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.  Returns
 a raw JSON Value.
The identification code of an object.
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 
 | |
Internal functions
unPermission :: Permission -> TextSource
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.