oauthenticated-0.3.0.0: Simple OAuth for http-client
Copyright(c) Joseph Abrahamson 2013
LicenseMIT
Maintainerme@jspha.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Network.OAuth.Simple

Description

Simplified Monadic interface for managing http-client and oauthenticated state. Re-exposes all of the functionality from Network.OAuth and Network.OAuth.ThreeLegged.

Synopsis

A monad for authenticated requests

Network.OAuth.Simple re-exports the Network.OAuth and Network.Oauth.ThreeLegged interfaces using the obvious StateT and ReaderT wrappers for tracking configuration, credentials, and random generator state. Managing Manager state is out of scope for this module, but since OAuthT is a monad transformer, it's easy enough to add another layer with the needed state.

oauth :: MonadIO m => Request -> OAuthT ty m Request Source #

Sign a request using fresh credentials.

runOAuthSimple :: OAuth ty a -> Cred ty -> IO a Source #

The simplest way to execute a set of authenticated requests. Produces invalid ThreeLegged requests---use runOAuth to provide Server and ThreeLegged configuration information.

More sophisticated interface

runOAuth :: OAuth ty a -> Cred ty -> Server -> ThreeLegged -> IO a Source #

runOAuthT :: MonadIO m => OAuthT ty m a -> Cred ty -> Server -> ThreeLegged -> m a Source #

Run's an OAuthT using a fresh EntropyPool.

newtype OAuthT ty m a Source #

Perform authenticated requests using a shared Manager and a particular set of Creds.

Constructors

OAuthT 

Fields

Instances

Instances details
MonadTrans (OAuthT ty) Source # 
Instance details

Defined in Network.OAuth.Simple

Methods

lift :: Monad m => m a -> OAuthT ty m a #

Monad m => Monad (OAuthT ty m) Source # 
Instance details

Defined in Network.OAuth.Simple

Methods

(>>=) :: OAuthT ty m a -> (a -> OAuthT ty m b) -> OAuthT ty m b #

(>>) :: OAuthT ty m a -> OAuthT ty m b -> OAuthT ty m b #

return :: a -> OAuthT ty m a #

Functor m => Functor (OAuthT ty m) Source # 
Instance details

Defined in Network.OAuth.Simple

Methods

fmap :: (a -> b) -> OAuthT ty m a -> OAuthT ty m b #

(<$) :: a -> OAuthT ty m b -> OAuthT ty m a #

Applicative m => Applicative (OAuthT ty m) Source # 
Instance details

Defined in Network.OAuth.Simple

Methods

pure :: a -> OAuthT ty m a #

(<*>) :: OAuthT ty m (a -> b) -> OAuthT ty m a -> OAuthT ty m b #

liftA2 :: (a -> b -> c) -> OAuthT ty m a -> OAuthT ty m b -> OAuthT ty m c #

(*>) :: OAuthT ty m a -> OAuthT ty m b -> OAuthT ty m b #

(<*) :: OAuthT ty m a -> OAuthT ty m b -> OAuthT ty m a #

MonadIO m => MonadIO (OAuthT ty m) Source # 
Instance details

Defined in Network.OAuth.Simple

Methods

liftIO :: IO a -> OAuthT ty m a #

MonadThrow m => MonadThrow (OAuthT ty m) Source # 
Instance details

Defined in Network.OAuth.Simple

Methods

throwM :: Exception e => e -> OAuthT ty m a #

MonadCatch m => MonadCatch (OAuthT ty m) Source # 
Instance details

Defined in Network.OAuth.Simple

Methods

catch :: Exception e => OAuthT ty m a -> (e -> OAuthT ty m a) -> OAuthT ty m a #

type OAuth ty = OAuthT ty IO Source #

OAuthT wrapped over IO.

Configuration management

upgradeCred :: (ResourceToken ty', Monad m) => Token ty' -> OAuthT ty m (Cred ty') Source #

upgrade :: (ResourceToken ty', Monad m) => Token ty' -> OAuthT ty' m a -> OAuthT ty m a Source #

Given a ResourceToken of some kind, run an inner OAuthT session with the same configuration but new credentials.

Configuration re-exports

OAuth Credentials

data Token ty Source #

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

Constructors

Token !Key !Secret 

Instances

Instances details
Eq (Token ty) Source # 
Instance details

Defined in Network.OAuth.Types.Credentials

Methods

(==) :: Token ty -> Token ty -> Bool #

(/=) :: Token ty -> Token ty -> Bool #

Data ty => Data (Token ty) Source # 
Instance details

Defined in Network.OAuth.Types.Credentials

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Token ty -> c (Token ty) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Token ty) #

toConstr :: Token ty -> Constr #

dataTypeOf :: Token ty -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Token ty)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Token ty)) #

gmapT :: (forall b. Data b => b -> b) -> Token ty -> Token ty #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Token ty -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Token ty -> r #

gmapQ :: (forall d. Data d => d -> u) -> Token ty -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Token ty -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Token ty -> m (Token ty) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Token ty -> m (Token ty) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Token ty -> m (Token ty) #

Ord (Token ty) Source # 
Instance details

Defined in Network.OAuth.Types.Credentials

Methods

compare :: Token ty -> Token ty -> Ordering #

(<) :: Token ty -> Token ty -> Bool #

(<=) :: Token ty -> Token ty -> Bool #

(>) :: Token ty -> Token ty -> Bool #

(>=) :: Token ty -> Token ty -> Bool #

max :: Token ty -> Token ty -> Token ty #

min :: Token ty -> Token ty -> Token ty #

Show (Token ty) Source # 
Instance details

Defined in Network.OAuth.Types.Credentials

Methods

showsPrec :: Int -> Token ty -> ShowS #

show :: Token ty -> String #

showList :: [Token ty] -> ShowS #

ToJSON (Token ty) Source #

Produces a JSON object using keys named oauth_token and oauth_token_secret.

Instance details

Defined in Network.OAuth.Types.Credentials

FromJSON (Token ty) Source #

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

Instance details

Defined in Network.OAuth.Types.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

Instances details
Eq (Cred ty) Source # 
Instance details

Defined in Network.OAuth.Types.Credentials

Methods

(==) :: Cred ty -> Cred ty -> Bool #

(/=) :: Cred ty -> Cred ty -> Bool #

Data ty => Data (Cred ty) Source # 
Instance details

Defined in Network.OAuth.Types.Credentials

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Cred ty -> c (Cred ty) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Cred ty) #

toConstr :: Cred ty -> Constr #

dataTypeOf :: Cred ty -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Cred ty)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Cred ty)) #

gmapT :: (forall b. Data b => b -> b) -> Cred ty -> Cred ty #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cred ty -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cred ty -> r #

gmapQ :: (forall d. Data d => d -> u) -> Cred ty -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Cred ty -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Cred ty -> m (Cred ty) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Cred ty -> m (Cred ty) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Cred ty -> m (Cred ty) #

Ord (Cred ty) Source # 
Instance details

Defined in Network.OAuth.Types.Credentials

Methods

compare :: Cred ty -> Cred ty -> Ordering #

(<) :: Cred ty -> Cred ty -> Bool #

(<=) :: Cred ty -> Cred ty -> Bool #

(>) :: Cred ty -> Cred ty -> Bool #

(>=) :: Cred ty -> Cred ty -> Bool #

max :: Cred ty -> Cred ty -> Cred ty #

min :: Cred ty -> Cred ty -> Cred ty #

Show (Cred ty) Source # 
Instance details

Defined in Network.OAuth.Types.Credentials

Methods

showsPrec :: Int -> Cred ty -> ShowS #

show :: Cred ty -> String #

showList :: [Cred ty] -> ShowS #

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.

Instances

Instances details
Data Client Source # 
Instance details

Defined in Network.OAuth.Types.Credentials

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Client -> c Client #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Client #

toConstr :: Client -> Constr #

dataTypeOf :: Client -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Client) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Client) #

gmapT :: (forall b. Data b => b -> b) -> Client -> Client #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Client -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Client -> r #

gmapQ :: (forall d. Data d => d -> u) -> Client -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Client -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Client -> m Client #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Client -> m Client #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Client -> m Client #

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.

Instances

Instances details
Data Temporary Source # 
Instance details

Defined in Network.OAuth.Types.Credentials

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Temporary -> c Temporary #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Temporary #

toConstr :: Temporary -> Constr #

dataTypeOf :: Temporary -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Temporary) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Temporary) #

gmapT :: (forall b. Data b => b -> b) -> Temporary -> Temporary #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Temporary -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Temporary -> r #

gmapQ :: (forall d. Data d => d -> u) -> Temporary -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Temporary -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Temporary -> m Temporary #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Temporary -> m Temporary #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Temporary -> m Temporary #

ResourceToken Temporary Source # 
Instance details

Defined in Network.OAuth.Types.Credentials

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.

Instances

Instances details
Data Permanent Source # 
Instance details

Defined in Network.OAuth.Types.Credentials

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Permanent -> c Permanent #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Permanent #

toConstr :: Permanent -> Constr #

dataTypeOf :: Permanent -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Permanent) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Permanent) #

gmapT :: (forall b. Data b => b -> b) -> Permanent -> Permanent #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Permanent -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Permanent -> r #

gmapQ :: (forall d. Data d => d -> u) -> Permanent -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Permanent -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Permanent -> m Permanent #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Permanent -> m Permanent #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Permanent -> m Permanent #

ResourceToken Permanent Source # 
Instance details

Defined in Network.OAuth.Types.Credentials

Creating Credentials

fromUrlEncoded :: ByteString -> Maybe (Bool, Token ty) Source #

Parses a www-form-urlencoded stream to produce a Token if possible. The first result value is whether or not the token data is OAuth 1.0a compatible.

>>> fromUrlEncoded "oauth_token=key&oauth_token_secret=secret"
Just (False, Token "key" "secret")
>>> fromUrlEncoded "oauth_token=key&oauth_token_secret=secret&oauth_callback_confirmed=true"
Just (True, Token "key" "secret")

OAuth Configuration

data Server Source #

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

Instances

Instances details
Eq Server Source # 
Instance details

Defined in Network.OAuth.Types.Params

Methods

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

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

Data Server Source # 
Instance details

Defined in Network.OAuth.Types.Params

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Server -> c Server #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Server #

toConstr :: Server -> Constr #

dataTypeOf :: Server -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Server) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Server) #

gmapT :: (forall b. Data b => b -> b) -> Server -> Server #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Server -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Server -> r #

gmapQ :: (forall d. Data d => d -> u) -> Server -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Server -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Server -> m Server #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Server -> m Server #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Server -> m Server #

Ord Server Source # 
Instance details

Defined in Network.OAuth.Types.Params

Show Server Source # 
Instance details

Defined in Network.OAuth.Types.Params

defaultServer :: Server Source #

The default Server parameterization uses OAuth recommended parameters.

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.

Instances

Instances details
Eq ParameterMethod Source # 
Instance details

Defined in Network.OAuth.Types.Params

Data ParameterMethod Source # 
Instance details

Defined in Network.OAuth.Types.Params

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParameterMethod -> c ParameterMethod #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ParameterMethod #

toConstr :: ParameterMethod -> Constr #

dataTypeOf :: ParameterMethod -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ParameterMethod) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ParameterMethod) #

gmapT :: (forall b. Data b => b -> b) -> ParameterMethod -> ParameterMethod #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParameterMethod -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParameterMethod -> r #

gmapQ :: (forall d. Data d => d -> u) -> ParameterMethod -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParameterMethod -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParameterMethod -> m ParameterMethod #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParameterMethod -> m ParameterMethod #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParameterMethod -> m ParameterMethod #

Ord ParameterMethod Source # 
Instance details

Defined in Network.OAuth.Types.Params

Show ParameterMethod Source # 
Instance details

Defined in Network.OAuth.Types.Params

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 

Instances

Instances details
Eq SignatureMethod Source # 
Instance details

Defined in Network.OAuth.Types.Params

Data SignatureMethod Source # 
Instance details

Defined in Network.OAuth.Types.Params

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SignatureMethod -> c SignatureMethod #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SignatureMethod #

toConstr :: SignatureMethod -> Constr #

dataTypeOf :: SignatureMethod -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SignatureMethod) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SignatureMethod) #

gmapT :: (forall b. Data b => b -> b) -> SignatureMethod -> SignatureMethod #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SignatureMethod -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SignatureMethod -> r #

gmapQ :: (forall d. Data d => d -> u) -> SignatureMethod -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SignatureMethod -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SignatureMethod -> m SignatureMethod #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SignatureMethod -> m SignatureMethod #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SignatureMethod -> m SignatureMethod #

Ord SignatureMethod Source # 
Instance details

Defined in Network.OAuth.Types.Params

Show SignatureMethod Source # 
Instance details

Defined in Network.OAuth.Types.Params

QueryValueLike SignatureMethod Source # 
Instance details

Defined in Network.OAuth.Types.Params

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

Instances details
Eq Version Source # 
Instance details

Defined in Network.OAuth.Types.Params

Methods

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

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

Data Version Source # 
Instance details

Defined in Network.OAuth.Types.Params

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Version -> c Version #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Version #

toConstr :: Version -> Constr #

dataTypeOf :: Version -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Version) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Version) #

gmapT :: (forall b. Data b => b -> b) -> Version -> Version #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r #

gmapQ :: (forall d. Data d => d -> u) -> Version -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Version -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Version -> m Version #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version #

Ord Version Source # 
Instance details

Defined in Network.OAuth.Types.Params

Show Version Source # 
Instance details

Defined in Network.OAuth.Types.Params

QueryValueLike Version Source #

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

Instance details

Defined in Network.OAuth.Types.Params

Three-Legged Authorization

Configuration types

data ThreeLegged Source #

Data parameterizing the "Three-legged OAuth" redirection-based authorization protocol. These parameters cover the protocol as described in the community editions OAuth Core 1.0 and OAuth Core 1.0a as well as RFC 5849.

Constructors

ThreeLegged 

Fields

  • temporaryTokenRequest :: Request

    Base Request for the "endpoint used by the client to obtain a set of Temporary Credentials" in the form of a Temporary Token. This request is automatically instantiated and performed during the first leg of the ThreeLegged authorization protocol.

  • resourceOwnerAuthorization :: Request

    Base Request for the "endpoint to which the resource owner is redirected to grant authorization". This request must be performed by the user granting token authorization to the client. Transmitting the parameters of this request to the user is out of scope of oauthenticated, but functions are provided to make it easier.

  • permanentTokenRequest :: Request

    Base Request for the "endpoint used by the client to request a set of token credentials using the set of Temporary Credentials". This request is also instantiated and performed by oauthenticated in order to produce a Permanent Token.

  • callback :: Callback

    The Callback parameter configures how the user is intended to communicate the Verifier back to the client.

Instances

Instances details
Show ThreeLegged Source # 
Instance details

Defined in Network.OAuth.ThreeLegged

parseThreeLegged :: String -> String -> String -> Callback -> Maybe ThreeLegged Source #

Convenience method for creating a ThreeLegged configuration from a trio of URLs and a Callback. Returns Nothing if one of the callback URLs could not be parsed correctly.

data Callback Source #

When performing the second leg of the three-leg token request workflow, the user must pass the oauth_verifier code back to the client. In order to ensure that this protocol is secure, OAuth demands that the client associates this "callback method" with the temporary credentials generated for the workflow. This Callback method may be a URL where the parameters are returned to or the string "oob" which indicates that the user is responsible for returning the oauth_verifier to the client OutOfBand.

Constructors

OutOfBand 
Callback Request 

Instances

Instances details
Show Callback Source # 
Instance details

Defined in Network.OAuth.Types.Params

QueryValueLike Callback Source #

Prints out in Epoch time format, a printed integer

Instance details

Defined in Network.OAuth.Types.Params

type Verifier = ByteString Source #

A Verifier is produced when a user authorizes a set of Temporary Creds. Using the Verifier allows the client to request Permanent Creds.

Actions

Example System

requestTokenProtocol :: (Functor m, MonadIO m, MonadCatch m) => Manager -> (URI -> m Verifier) -> OAuthT Client m (Either TokenRequestFailure (Cred Permanent)) Source #

Run a full Three-legged authorization protocol using the simple interface of this module. This is similar to the requestTokenProtocol in Network.OAuth.ThreeLegged, but offers better error handling due in part to the easier management of configuration state.