hoauth-0.3.2: A Haskell implementation of OAuth 1.0a protocol.

Network.OAuth.Consumer

Contents

Description

A Haskell library that implements oauth authentication protocol as defined in http://tools.ietf.org/html/draft-hammer-oauth-10.

According to the RFC [1]: OAuth provides a method for clients to access server resources on behalf of a resource owner (such as a different client or an end- user). It also provides a process for end-users to authorize third- party access to their server resources without sharing their credentials (typically, a username and password pair), using user- agent redirections.

The following code should perform a request using 3 legged oauth, provided the parameters are defined correctly:

  reqUrl    = fromJust . parseURL $ "https://service.provider/request_token"
  accUrl    = fromJust . parseURL $ "https://service.provider/access_token"
  srvUrl    = fromJust . parseURL $ "http://service/path/to/resource/"
  authUrl   = ("http://service.provider/authorize?oauth_token="++) . findWithDefault ("oauth_token","ERROR") . oauthParams
  app       = Application "consumerKey" "consumerSec" OOB
  response  = runOAuthM (fromApplication app) $ do { signRq2 PLAINTEXT Nothing reqUrl >>= oauthRequest CurlHttpClient
                                                   ; cliAskAuthorization authUrl
                                                   ; signRq2 PLAINTEXT Nothing accUrl >>= oauthRequest CurlHttpClient
                                                   ; signRq2 HMACSHA1 (Just $ Realm "realm") srvUrl >>= serviceRequest CurlHttpClient
                                                   }

Synopsis

Types

data OAuthRequest Source

A request that is ready to be performed, i.e., that contains authorization headers.

data Token Source

The OAuth Token.

Constructors

TwoLegg

This token is used to perform 2 legged OAuth requests.

ReqToken

The service provider has granted you the request token but the user has not yet authorized your application. You need to exchange this token by a proper AccessToken, but this may only happen after user has granted you permission to do so.

AccessToken

This is a proper 3 legged OAuth. The difference between this and ReqToken is that user has authorized your application and you can perform requests on behalf of that user.

Instances

data Application Source

Identifies the application.

data OAuthCallback Source

Callback used in oauth authorization

Constructors

URL String 
OOB 

data SigMethod Source

Available signature methods.

Constructors

PLAINTEXT

The PLAINTEXT consumer_key token_secret method does not provide any security protection and SHOULD only be used over a secure channel such as HTTPS. It does not use the Signature Base String.

HMACSHA1

The HMAC_SHA1 consumer_key token_secret signature method uses the HMAC-SHA1 signature algorithm as defined in http://tools.ietf.org/html/rfc2104 where the Signature Base String is the text and the key is the concatenated values (each first encoded per Parameter Encoding) of the Consumer Secret and Token Secret, separated by an & character (ASCII code 38) even if empty.

RSASHA1 PrivateKey

The RSA-SHA1 signature method uses the RSASSA-PKCS1-v1_5 signature algorithm as defined in [RFC3447], Section 8.2 (also known as PKCS#1), using SHA-1 as the hash function for EMSA-PKCS1-v1_5. To use this method, the client MUST have established client credentials with the server that included its RSA public key (in a manner that is beyond the scope of this specification).

newtype Realm Source

The optional authentication realm. Refer to http://oauth.net/core/1.0/#auth_header_authorization for more information.

Constructors

Realm 

Fields

unRealm :: String
 

Instances

newtype Nonce Source

Random string that is unique amongst requests. Refer to http://oauth.net/core/1.0/#nonce for more information.

Constructors

Nonce 

Fields

unNonce :: String
 

Instances

newtype Timestamp Source

Unix timestamp (seconds since epoch). Refer to http://oauth.net/core/1.0/#nonce for more information.

Constructors

Timestamp 

Fields

unTimestamp :: String
 

OAuthMonadT related functions

runOAuth :: Monad m => (String -> m a) -> Token -> OAuthMonadT m a -> m aSource

Execute the oauth monad using a given error handler

runOAuthM :: Monad m => Token -> OAuthMonadT m a -> m aSource

Execute the oauth monad and returns the value it produced using fail as the error handler.

oauthRequest :: (HttpClient c, MonadIO m) => c -> OAuthRequest -> OAuthMonadT m TokenSource

Executes an oauth request which is intended to upgrade/refresh the current token.

packRq :: Request -> OAuthRequestSource

Simply create the OAuthRequest but adds no Authorization header.

signRq :: MonadIO m => Token -> SigMethod -> Maybe Realm -> Request -> m OAuthRequestSource

Complete the request with authorization headers.

signRq2 :: MonadIO m => SigMethod -> Maybe Realm -> Request -> OAuthMonadT m OAuthRequestSource

Complete the request with authorization headers.

serviceRequest :: (HttpClient c, MonadIO m) => c -> OAuthRequest -> OAuthMonadT m ResponseSource

Performs a signed request with the available token.

cliAskAuthorization :: MonadIO m => (Token -> String) -> OAuthMonadT m ()Source

Probably this is just useful for testing. It asks the user (stdout/stdin) to authorize the application and provide the oauth_verifier.

ignite :: MonadIO m => Application -> OAuthMonadT m ()Source

Transforms an application into a token.

getToken :: Monad m => OAuthMonadT m TokenSource

Extracts the token from the OAuthMonadT.

putToken :: Monad m => Token -> OAuthMonadT m ()Source

Alias to the put function.

Token related functions

twoLegged :: Token -> BoolSource

Returns true if the token is able to perform 2-legged oauth requests.

threeLegged :: Token -> BoolSource

Tests whether or not the current token is able to perform 3-legged requests.

signature :: SigMethod -> Token -> Request -> StringSource

Signs a request using a given signature method. This expects the request to be a valid request already (for instance, none and timestamp are not set).

injectOAuthVerifier :: String -> Token -> TokenSource

Injects the oauth_verifier into the token. Usually this means the user has authorized the app to access his data.

fromApplication :: Application -> TokenSource

Creates a TwoLegg token from an application

fromResponse :: Response -> Token -> Either String TokenSource

Receives a response possibly from a service provider and updates the token. As a matter effect, assumes the content-type is application/x-www-form-urlencoded (because some service providers send it as text/plain) and if the status is [200..300) updates the token accordingly.

authorization :: SigMethod -> Maybe Realm -> Nonce -> Timestamp -> Token -> Request -> StringSource

Computes the authorization header and updates the request.