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.Types.Params

Description

OAuth Parameters

OAuth 1.0 operates by creating a set of "oauth parameters" here called Oa which augment a request with OAuth specific metadata. They may be used to augment the request by one of several ParameterMethods.

Synopsis

Documentation

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

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

newtype Timestamp Source #

An Epoch time format timestamp.

Constructors

Timestamp UTCTime 

Instances

Instances details
Eq Timestamp Source # 
Instance details

Defined in Network.OAuth.Types.Params

Data Timestamp 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) -> Timestamp -> c Timestamp #

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

toConstr :: Timestamp -> Constr #

dataTypeOf :: Timestamp -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Timestamp Source # 
Instance details

Defined in Network.OAuth.Types.Params

Show Timestamp Source # 
Instance details

Defined in Network.OAuth.Types.Params

QueryValueLike Timestamp Source #

Prints out in Epoch time format, a printed integer

Instance details

Defined in Network.OAuth.Types.Params

timestampFromSeconds :: Integer -> Timestamp Source #

Create a Timestamp deterministically from a POSIX Epoch Time.

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.

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.

data Workflow Source #

Some special OAuth requests use extra oauth_* parameters. For example, when requesting a temporary credential, it's necessary that a oauth_callback parameter be specified. WorkflowParams allows these extra parameters to be specified.

Constructors

Standard

No special OAuth parameters needed

TemporaryTokenRequest Callback 
PermanentTokenRequest ByteString

Includes the oauth_verifier

Instances

Instances details
Show Workflow Source # 
Instance details

Defined in Network.OAuth.Types.Params

data OaPin Source #

The OaPin is a set of impure OAuth parameters which are generated for each request in order to ensure uniqueness and temporality.

Constructors

OaPin 

Instances

Instances details
Eq OaPin Source # 
Instance details

Defined in Network.OAuth.Types.Params

Methods

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

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

Data OaPin 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) -> OaPin -> c OaPin #

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

toConstr :: OaPin -> Constr #

dataTypeOf :: OaPin -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord OaPin Source # 
Instance details

Defined in Network.OAuth.Types.Params

Methods

compare :: OaPin -> OaPin -> Ordering #

(<) :: OaPin -> OaPin -> Bool #

(<=) :: OaPin -> OaPin -> Bool #

(>) :: OaPin -> OaPin -> Bool #

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

max :: OaPin -> OaPin -> OaPin #

min :: OaPin -> OaPin -> OaPin #

Show OaPin Source # 
Instance details

Defined in Network.OAuth.Types.Params

Methods

showsPrec :: Int -> OaPin -> ShowS #

show :: OaPin -> String #

showList :: [OaPin] -> ShowS #

emptyPin :: OaPin Source #

An "empty" pin useful for testing. This OaPin is referentially transparent and thus has none of the necessary security features---it should never be used in an actual transaction!

freshPin :: (MonadRandom m, MonadIO m) => m OaPin Source #

Creates a new, unique, unpredictable OaPin. This should be used quickly as dependent on the OAuth server settings it may expire.

emptyOa :: Cred ty -> Oa ty Source #

Uses emptyPin to create an empty set of params Oa.

freshOa :: (MonadRandom m, MonadIO m) => Cred ty -> m (Oa ty) Source #

Uses freshPin to create a fresh, default set of params Oa.

data Oa ty Source #

The Oa parameters include all the OAuth information specific to a single request. They are not sufficient information by themselves to generate the entire OAuth request but instead must be augmented with Server information.

Constructors

Oa 

Fields

Instances

Instances details
Show (Oa ty) Source # 
Instance details

Defined in Network.OAuth.Types.Params

Methods

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

show :: Oa ty -> String #

showList :: [Oa ty] -> ShowS #