Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- 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
- newtype Credential = Credential {
- unCredential :: [(ByteString, ByteString)]
- newtype OAuthException = OAuthException String
- data AccessTokenRequest
- defaultAccessTokenRequest :: OAuth -> Credential -> Manager -> AccessTokenRequest
- accessTokenAddAuth :: AccessTokenRequest -> ByteString -> Credential -> Request -> Request
- accessTokenRequestHook :: AccessTokenRequest -> Request -> Request
- accessTokenOAuth :: AccessTokenRequest -> OAuth
- accessTokenTemporaryCredential :: AccessTokenRequest -> Credential
- accessTokenManager :: AccessTokenRequest -> Manager
- 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
- checkOAuth :: MonadIO m => OAuth -> Credential -> Request -> ExceptT OAuthException m Request
- 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
- addAuthBody :: a -> Credential -> Request -> Request
- 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
- getAccessTokenWith :: MonadIO m => AccessTokenRequest -> m (Either (Response ByteString) 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.
Instances
Eq OAuth Source # | |
Data OAuth Source # | |
Defined in Web.Authenticate.OAuth gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OAuth -> c OAuth # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OAuth # dataTypeOf :: OAuth -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OAuth) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OAuth) # gmapT :: (forall b. Data b => b -> b) -> OAuth -> OAuth # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OAuth -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OAuth -> r # gmapQ :: (forall d. Data d => d -> u) -> OAuth -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OAuth -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OAuth -> m OAuth # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OAuth -> m OAuth # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OAuth -> m OAuth # | |
Read OAuth Source # | |
Show OAuth Source # | |
Default OAuth Source # | |
Defined in Web.Authenticate.OAuth |
Default value for OAuth datatype. You must specify at least oauthServerName, URIs and Tokens.
oauthServerName :: OAuth -> String Source #
Service name (default: ""
)
oauthRequestUri :: OAuth -> String Source #
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 -> String Source #
Uri to obtain access token (default: ""
).
You MUST specify if you use getAcessToken
or getAccessToken'
or getAccessTokenWith
;
otherwise you can just leave this empty.
oauthAuthorizeUri :: OAuth -> String Source #
Uri to authorize (default: ""
).
You MUST specify if you use authorizeUrl
or authorizeZUrl'
;
otherwise you can just leave this empty.
oauthSignatureMethod :: OAuth -> SignMethod Source #
Signature Method (default: HMACSHA1
)
oauthConsumerKey :: OAuth -> ByteString Source #
Consumer key (You MUST specify)
oauthConsumerSecret :: OAuth -> ByteString Source #
Consumer Secret (You MUST specify)
oauthCallback :: OAuth -> Maybe ByteString Source #
Callback uri to redirect after authentication (default: Nothing
)
oauthRealm :: OAuth -> Maybe ByteString Source #
Optional authorization realm (default: Nothing
)
oauthVersion :: OAuth -> OAuthVersion Source #
OAuth spec version (default: OAuth10a
)
data OAuthVersion Source #
OAuth10 | OAuth protocol ver 1.0 (no oauth_verifier; differs from RFC 5849). |
OAuth10a | OAuth protocol ver 1.0a. This corresponds to community's 1.0a spec and RFC 5849. |
Instances
data SignMethod Source #
Data type for signature method.
PLAINTEXT | |
HMACSHA1 | |
HMACSHA256 | |
HMACSHA512 | |
RSASHA1 PrivateKey | |
RSASHA256 PrivateKey | |
RSASHA512 PrivateKey |
Instances
newtype Credential Source #
Data type for credential.
Credential | |
|
Instances
newtype OAuthException Source #
Instances
Access token request
data AccessTokenRequest Source #
Data type for getAccessTokenWith method.
You can create values of this type using defaultAccessTokenRequest
.
Since 1.5.1
defaultAccessTokenRequest :: OAuth -> Credential -> Manager -> AccessTokenRequest Source #
Create a value of type AccessTokenRequest
with default values filled in.
Note that this is a settings type. More information on usage can be found at: http://www.yesodweb.com/book/settings-types.
Since 1.5.1
accessTokenAddAuth :: AccessTokenRequest -> ByteString -> Credential -> Request -> Request Source #
add auth hook.
Default: addAuthHeader
Since 1.5.1
accessTokenRequestHook :: AccessTokenRequest -> Request -> Request Source #
Request Hook.
Default: id
Since 1.5.1
accessTokenOAuth :: AccessTokenRequest -> OAuth Source #
OAuth Application
Since 1.5.1
accessTokenTemporaryCredential :: AccessTokenRequest -> Credential Source #
Temporary Credential (with oauth_verifier if >= 1.0a)
Since 1.5.1
accessTokenManager :: AccessTokenRequest -> Manager Source #
Manager
Since 1.5.1
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 :: Credential Source #
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 -> Credential Source #
Convenient method for inserting multiple parameters into credential.
injectVerifier :: ByteString -> Credential -> Credential Source #
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 ByteString Source #
Generate OAuth signature. Used by signOAuth
.
checkOAuth :: MonadIO m => OAuth -> Credential -> Request -> ExceptT OAuthException m Request Source #
Test existing OAuth signature. Since 1.5.2
Url & operation for authentication
Temporary credentials
getTemporaryCredential Source #
:: MonadIO m | |
=> OAuth | OAuth Application |
-> Manager | |
-> m Credential | Temporary Credential (Request Token & Secret). |
Get temporary credential for requesting acces token.
getTemporaryCredentialWithScope Source #
:: 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.
getTemporaryCredentialProxy Source #
:: 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.
Attaching auth to requests
addAuthBody :: a -> Credential -> Request -> Request Source #
Place the authentication information in a URL encoded body instead of the Authorization header.
Note that the first parameter is used for realm in addAuthHeader, and this function needs the same type. The parameter, however, is unused.
Since 1.5.1
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.
getTokenCredentialProxy Source #
:: 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) |
:: MonadIO m | |
=> AccessTokenRequest | extensible parameters |
-> m (Either (Response ByteString) Credential) | Token Credential (Access Token & Secret) or the conduit response on failures |
Utility Methods
paramEncode :: ByteString -> ByteString Source #
Encode a string using the percent encoding method for OAuth.