oauthenticated-0.0.5: Simple OAuth client code built atop http-conduit

Portabilitynon-portable
Stabilityexperimental
Maintainerme@jspha.com
Safe HaskellNone

Network.OAuth

Contents

Description

Network.OAuth provides simple OAuth signed requests atop Network.HTTP.Client. This module exports a simplified interface atop the monadic interface defined in Network.OAuth.Stateful.

If more control is needed, the low-level functions for creating, customizing, and managing OAuth Credentials, Tokens, and parameter sets (Oa) are using them to sign Requests are available in Network.OAuth.Types.Params, Network.OAuth.Types.Credentials, and Network.OAuth.Signing.

Synopsis

The basic monadic API

oauth :: MonadIO m => Request -> OAuthT ty m RequestSource

Generate default OAuth parameters and use them to sign a request. This is the simplest OAuth method.

Simplified requests layer

simpleOAuth :: (MonadIO m, MonadCatch m) => String -> Params -> OAuthT ty m (Response ByteString)Source

Send an OAuth GET request to a particular URI. Throws an exception if the URI cannot be parsed or if errors occur during the request.

data Params Source

Params quickly set the parameterization of a Request, either a GET request with a query string or a POST request with a www-form-urlencoded body.

type Query = [QueryItem]

Query.

General form: a=b&c=d, but if the value is Nothing, it becomes a&c=d.

type QueryItem = (ByteString, Maybe ByteString)

Query item

OAuth Monad

data OAuthT ty m a Source

A simple monad suitable for basic OAuth requests.

Instances

MonadTrans (OAuthT ty) 
Monad m => Monad (OAuthT ty m) 
Functor m => Functor (OAuthT ty m) 
(Monad m, Functor m) => Applicative (OAuthT ty m) 
MonadIO m => MonadIO (OAuthT ty m) 

runOAuthT :: (MonadIO m, MonadCatch m) => Cred ty -> Server -> OAuthT ty m a -> m aSource

runOAuthT' :: (MonadIO m, MonadCatch m) => ManagerSettings -> Cred ty -> Server -> OAuthT ty m a -> m aSource

OAuth Configuration

data Server Source

The Server information contains details which parameterize how a particular server wants to interpret OAuth requests.

data ParameterMethod Source

The OAuth spec suggest that the OAuth parameter be passed via the Authorization header, but allows for other methods of transmission (see section 3.5. Parameter Transmission) so we select the 'Server'\'s preferred method with this type.

Constructors

AuthorizationHeader

Place the Oa parameters in the Authorization HTTP header.

RequestEntityBody

Augment the www-form-urlencoded request body with Oa parameters.

QueryString

Augment the www-form-urlencoded query string with Oa parameters.

data SignatureMethod Source

OAuth culminates in the creation of the oauth_signature which signs and authenticates the request using the secret components of a particular OAuth Cred.

Several methods exist for generating these signatures, the most popular being HmacSha1.

Constructors

HmacSha1 
Plaintext 

data Version Source

OAuth has progressed through several versions since its inception. In particular, there are two community editions "OAuth Core 1.0" (2007) and "OAuth Core 1.0a" (2009) along with the IETF Official version RFC 5849 (2010) which is confusingly named OAuth 1.0.

/Servers which only implement the obsoleted community edition "OAuth Core 1.0" are susceptible to a session fixation attack./

If at all possible, choose the RFC 5849 version (the OAuth1 value) as it is the modern standard. Some servers may only be compliant with an earlier OAuth version---this should be tested against each server, in particular the protocols defined in Network.OAuth.ThreeLegged.

Constructors

OAuthCommunity1

OAuth Core 1.0 Community Edition

OAuthCommunity1a

OAuth Core 1.0 Community Edition, Revision A

OAuth1

RFC 5849

Instances

Eq Version 
Data Version 
Ord Version 
Show Version 
Typeable Version 
QueryValueLike Version

All three OAuth 1.0 versions confusingly report the same version number.

defaultServer :: ServerSource

The default Server parameterization uses OAuth recommended parameters.

Credential managerment

data Permanent Source

Permanent Tokens and Credentials are the primary means of accessing server resources. They must be maintained by the client for each user who authorizes that client to access resources on their behalf.

data Temporary Source

Temporary Tokens and Credentials are created during authorization protocols and are rarely meant to be kept for more than a few minutes. Typically they are authorized to access only a very select set of server resources. During "three-legged authorization" in OAuth 1.0 they are used to generate the authorization request URI the client sends and, after that, in the Permanent Token request.

data Client Source

Client Credentials and Tokens are assigned to a particular client by the server and are used for all requests sent by that client. They form the core component of resource specific credentials.

data Cred ty Source

Credentials pair a Client Token and either a Temporary or Permanent token corresponding to a particular set of user resources on the server.

Instances

Typeable1 Cred 
Eq (Cred ty) 
Data ty => Data (Cred ty) 
Ord (Cred ty) 
Show (Cred ty) 

data Token ty Source

Tokens are public, private key pairs and come in many varieties, Client, Temporary, and Permanent.

Constructors

Token !Key !Secret 

Instances

Typeable1 Token 
Eq (Token ty) 
Data ty => Data (Token ty) 
Ord (Token ty) 
Show (Token ty) 
ToJSON (Token ty)

Produces a JSON object using keys named oauth_token and oauth_token_secret.

FromJSON (Token ty)

Parses a JSON object with keys oauth_token and oauth_token_secret, the standard format for OAuth 1.0.

Access lenses

clientToken :: Lens (Cred ty) (Cred ty) (Token Client) (Token Client)Source

All Creds have Client Token information.

resourceToken :: (ResourceToken ty, ResourceToken ty') => Lens (Cred ty) (Cred ty') (Token ty) (Token ty')Source

Some Creds have resource Token information, i.e. either Temporary or Permanent credentials. This lens can be used to change the type of a Cred.