| Copyright | (c) Joseph Abrahamson 2013 |
|---|---|
| License | MIT |
| Maintainer | me@jspha.com |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell2010 |
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
- data ParameterMethod
- data SignatureMethod
- data Version
- data Callback
- newtype Timestamp = Timestamp UTCTime
- timestampFromSeconds :: Integer -> Timestamp
- data Server = Server {}
- defaultServer :: Server
- type Verifier = ByteString
- data Workflow
- data OaPin = OaPin {}
- emptyPin :: OaPin
- freshPin :: (MonadRandom m, MonadIO m) => m OaPin
- emptyOa :: Cred ty -> Oa ty
- freshOa :: (MonadRandom m, MonadIO m) => Cred ty -> m (Oa ty)
- data Oa ty = Oa {}
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 |
| RequestEntityBody | Augment the |
| QueryString | Augment the |
Instances
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.
Instances
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 Source # | |
| Data Version Source # | |
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 # | |
Defined in Network.OAuth.Types.Params | |
| Show Version Source # | |
| QueryValueLike Version Source # | All three OAuth 1.0 versions confusingly report the same version number. |
Defined in Network.OAuth.Types.Params Methods toQueryValue :: Version -> Maybe ByteString # | |
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.
Instances
| Show Callback Source # | |
| QueryValueLike Callback Source # | Prints out in Epoch time format, a printed integer |
Defined in Network.OAuth.Types.Params Methods toQueryValue :: Callback -> Maybe ByteString # | |
An Epoch time format timestamp.
Instances
| Eq Timestamp Source # | |
| Data Timestamp Source # | |
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 # | |
| Show Timestamp Source # | |
| QueryValueLike Timestamp Source # | Prints out in Epoch time format, a printed integer |
Defined in Network.OAuth.Types.Params Methods toQueryValue :: Timestamp -> Maybe ByteString # | |
timestampFromSeconds :: Integer -> Timestamp Source #
Create a Timestamp deterministically from a POSIX Epoch Time.
The Server information contains details which parameterize how a
particular server wants to interpret OAuth requests.
Constructors
| Server | |
Fields | |
Instances
| Eq Server Source # | |
| Data Server Source # | |
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 # | |
| Show Server Source # | |
defaultServer :: Server Source #
The default Server parameterization uses OAuth recommended parameters.
type Verifier = ByteString 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 |
The OaPin is a set of impure OAuth parameters which are generated for each
request in order to ensure uniqueness and temporality.
Constructors
| OaPin | |
Fields
| |
Instances
| Eq OaPin Source # | |
| Data OaPin Source # | |
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 # 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 # | |
| Show 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.