Safe Haskell | None |
---|
- data OAuth
- def :: Default a => a
- newOAuth :: OAuth
- oauthServerName :: OAuth -> String
- oauthRequestUri :: OAuth -> String
- oauthAccessTokenUri :: OAuth -> String
- oauthAuthorizeUri :: OAuth -> String
- oauthSignatureMethod :: OAuth -> SignMethod
- oauthConsumerKey :: OAuth -> ByteString
- oauthConsumerSecret :: OAuth -> ByteString
- oauthCallback :: OAuth -> Maybe ByteString
- oauthRealm :: OAuth -> Maybe ByteString
- oauthVersion :: OAuth -> OAuthVersion
- data OAuthVersion
- data SignMethod
- = PLAINTEXT
- | HMACSHA1
- | RSASHA1 PrivateKey
- data Credential = Credential {
- unCredential :: [(ByteString, ByteString)]
- data OAuthException = OAuthException String
- newCredential :: ByteString -> ByteString -> Credential
- emptyCredential :: Credential
- insert :: ByteString -> ByteString -> Credential -> Credential
- delete :: ByteString -> Credential -> Credential
- inserts :: [(ByteString, ByteString)] -> Credential -> Credential
- injectVerifier :: ByteString -> Credential -> Credential
- signOAuth :: MonadIO m => OAuth -> Credential -> Request -> m Request
- genSign :: MonadIO m => OAuth -> Credential -> Request -> m ByteString
- getTemporaryCredential :: MonadIO m => OAuth -> Manager -> m Credential
- getTemporaryCredentialWithScope :: MonadIO m => ByteString -> OAuth -> Manager -> m Credential
- getTemporaryCredentialProxy :: MonadIO m => Maybe Proxy -> OAuth -> Manager -> m Credential
- getTemporaryCredential' :: MonadIO m => (Request -> Request) -> OAuth -> Manager -> m Credential
- authorizeUrl :: OAuth -> Credential -> String
- authorizeUrl' :: (OAuth -> Credential -> SimpleQuery) -> OAuth -> Credential -> String
- getAccessToken :: MonadIO m => OAuth -> Credential -> Manager -> m Credential
- getAccessTokenProxy :: MonadIO m => Maybe Proxy -> OAuth -> Credential -> Manager -> m Credential
- getTokenCredential :: MonadIO m => OAuth -> Credential -> Manager -> m Credential
- getTokenCredentialProxy :: MonadIO m => Maybe Proxy -> OAuth -> Credential -> Manager -> m Credential
- getAccessToken' :: MonadIO m => (Request -> Request) -> OAuth -> Credential -> Manager -> m Credential
- paramEncode :: ByteString -> ByteString
- addScope :: ByteString -> Request -> Request
- addMaybeProxy :: Maybe Proxy -> Request -> Request
Data types
Data type for OAuth client (consumer).
The constructor for this data type is not exposed.
Instead, you should use the def
method or newOAuth
function to retrieve a default instance,
and then use the records below to make modifications.
This approach allows us to add configuration options without breaking backwards compatibility.
Default value for OAuth datatype. You must specify at least oauthServerName, URIs and Tokens.
oauthServerName :: OAuth -> StringSource
Service name (default: ""
)
oauthRequestUri :: OAuth -> StringSource
URI to request temporary credential (default: ""
).
You MUST specify if you use getTemporaryCredential'
, getTemporaryCredentialProxy
or getTemporaryCredential
; otherwise you can just leave this empty.
oauthAccessTokenUri :: OAuth -> StringSource
Uri to obtain access token (default: ""
).
You MUST specify if you use getAcessToken
or getAccessToken'
;
otherwise you can just leave this empty.
oauthAuthorizeUri :: OAuth -> StringSource
Uri to authorize (default: ""
).
You MUST specify if you use authorizeUrl
or authorizeZUrl'
;
otherwise you can just leave this empty.
oauthSignatureMethod :: OAuth -> SignMethodSource
Signature Method (default: HMACSHA1
)
oauthConsumerKey :: OAuth -> ByteStringSource
Consumer key (You MUST specify)
oauthConsumerSecret :: OAuth -> ByteStringSource
Consumer Secret (You MUST specify)
oauthCallback :: OAuth -> Maybe ByteStringSource
Callback uri to redirect after authentication (default: Nothing
)
oauthRealm :: OAuth -> Maybe ByteStringSource
Optional authorization realm (default: Nothing
)
oauthVersion :: OAuth -> OAuthVersionSource
OAuth spec version (default: OAuth10a
)
data OAuthVersion Source
data SignMethod Source
Data type for signature method.
data Credential Source
Data type for redential.
Credential | |
|
data OAuthException Source
Operations for credentials
:: ByteString | value for oauth_token |
-> ByteString | value for oauth_token_secret |
-> Credential |
Convenient function to create Credential
with OAuth Token and Token Secret.
emptyCredential :: CredentialSource
Empty credential.
:: ByteString | Parameter Name |
-> ByteString | Value |
-> Credential | Credential |
-> Credential | Result |
Insert an oauth parameter into given Credential
.
:: ByteString | Parameter name |
-> Credential | Credential |
-> Credential | Result |
Remove an oauth parameter for key from given Credential
.
inserts :: [(ByteString, ByteString)] -> Credential -> CredentialSource
Convenient method for inserting multiple parameters into credential.
injectVerifier :: ByteString -> Credential -> CredentialSource
Insert oauth-verifier
on a Credential
.
Signature
:: MonadIO m | |
=> OAuth | OAuth Application |
-> Credential | Credential |
-> Request | Original Request |
-> m Request | Signed OAuth Request |
Add OAuth headers & sign to Request
.
genSign :: MonadIO m => OAuth -> Credential -> Request -> m ByteStringSource
Generate OAuth signature. Used by signOAuth
.
Url & operation for authentication
Temporary credentials
:: MonadIO m | |
=> OAuth | OAuth Application |
-> Manager | |
-> m Credential | Temporary Credential (Request Token & Secret). |
Get temporary credential for requesting acces token.
getTemporaryCredentialWithScopeSource
:: MonadIO m | |
=> ByteString | Scope parameter string |
-> OAuth | OAuth Application |
-> Manager | |
-> m Credential | Temporay Credential (Request Token & Secret). |
Get temporary credential for requesting access token with Scope parameter.
getTemporaryCredentialProxySource
:: MonadIO m | |
=> Maybe Proxy | Proxy |
-> OAuth | OAuth Application |
-> Manager | |
-> m Credential | Temporary Credential (Request Token & Secret). |
Get temporary credential for requesting access token via the proxy.
Authorization URL
:: OAuth | OAuth Application |
-> Credential | Temporary Credential (Request Token & Secret) |
-> String | URL to authorize |
URL to obtain OAuth verifier.
:: (OAuth -> Credential -> SimpleQuery) | |
-> OAuth | OAuth Application |
-> Credential | Temporary Credential (Request Token & Secret) |
-> String | URL to authorize |
Convert OAuth and Credential to URL to authorize. This takes function to choice parameter to pass to the server other than oauth_callback or oauth_token.
Finishing authentication
:: MonadIO m | |
=> OAuth | OAuth Application |
-> Credential | Temporary Credential (with oauth_verifier if >= 1.0a) |
-> Manager | |
-> m Credential | Token Credential (Access Token & Secret) |
Get Access token.
:: MonadIO m | |
=> Maybe Proxy | Proxy |
-> OAuth | OAuth Application |
-> Credential | Temporary Credential (with oauth_verifier if >= 1.0a) |
-> Manager | |
-> m Credential | Token Credential (Access Token & Secret) |
Get Access token via the proxy.
:: MonadIO m | |
=> OAuth | OAuth Application |
-> Credential | Temporary Credential (with oauth_verifier if >= 1.0a) |
-> Manager | |
-> m Credential | Token Credential (Access Token & Secret) |
Get Access token.
:: MonadIO m | |
=> Maybe Proxy | Proxy |
-> OAuth | OAuth Application |
-> Credential | Temporary Credential (with oauth_verifier if >= 1.0a) |
-> Manager | |
-> m Credential | Token Credential (Access Token & Secret) |
Get Access token via the proxy.
:: MonadIO m | |
=> (Request -> Request) | Request Hook |
-> OAuth | OAuth Application |
-> Credential | Temporary Credential (with oauth_verifier if >= 1.0a) |
-> Manager | |
-> m Credential | Token Credential (Access Token & Secret) |
Utility Methods
paramEncode :: ByteString -> ByteStringSource
Encode a string using the percent encoding method for OAuth.
addScope :: ByteString -> Request -> RequestSource