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.Credentials

Description

Credentials, Creds, are built from Tokens, public/private key pairs, and come in 3 varieties.

  • Client: Represents a particular client or consumer, used as part of every transaction that client signs.
  • Temporary: Resource token representing a short-lived grant to access a restricted set of server resources on behalf of the user. Typically used as part of a authorization negotiation protocol.
  • Permanent: Resource token representing a long-lived grant to access an authorized set of server resources on behalf of the user. Outside of access negotiation this is the most common kind of resource Token.
Synopsis

Tokens and their parameterization

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

type Key = ByteString Source #

Token Keys are public keys which allow a server to uniquely identify a particular Token.

type Secret = ByteString Source #

Token Secrets are private keys which the Token uses for cryptographic purposes.

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

class ResourceToken tk Source #

Instances

Instances details
ResourceToken Permanent Source # 
Instance details

Defined in Network.OAuth.Types.Credentials

ResourceToken Temporary Source # 
Instance details

Defined in Network.OAuth.Types.Credentials

Deserialization

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")

Credentials and credential construction

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 #

upgradeCred :: ResourceToken tk => Token tk -> Cred tk' -> Cred tk Source #

Accessors

key :: Functor f => (Key -> f Key) -> Token ty -> f (Token ty) Source #

Lens on the key component of a Token.

secret :: Functor f => (Secret -> f Secret) -> Token ty -> f (Token ty) Source #

Lens on the key secret component of a Token.

clientToken :: Functor f => (Token Client -> f (Token Client)) -> Cred ty -> f (Cred ty) Source #

A lens on the client Token in any Cred.

resourceToken :: (ResourceToken ty, ResourceToken ty', Functor f) => (Token ty -> f (Token ty')) -> Cred ty -> f (Cred ty') Source #

A lens focused on the resource Token when available. The only instances of ResourceToken are Temporary and Permanent. This can be used to upgrade Temporary Creds to Permanent Creds.

getResourceTokenDef :: Cred ty -> Token ty Source #

OAuth assumes that, by default, any credential has a resource Token that is by default completely blank. In this way we can talk about the resource Token of even Client Creds.

>>> getResourceTokenDef (clientCred $ Token "key" "secret")
Token "" ""

signingKey :: Cred ty -> ByteString Source #

Produce a signingKey from a set of credentials. This is a URL encoded string built from the client secret and the token secret.

If no token secret exists then the blank string is used.

\secret -> signingKey (clientCred $ Token "key" secret) == (pctEncode secret <> "&" <> "")