{-# LANGUAGE OverloadedStrings #-}
module Yesod.Auth.OAuth2.Bitbucket
( oauth2Bitbucket
, oauth2BitbucketScoped
)
where
import Yesod.Auth.OAuth2.Prelude
import qualified Data.Text as T
newtype User = User Text
instance FromJSON User where
parseJSON = withObject "User" $ \o -> User <$> o .: "uuid"
pluginName :: Text
pluginName = "bitbucket"
defaultScopes :: [Text]
defaultScopes = ["account"]
oauth2Bitbucket :: YesodAuth m => Text -> Text -> AuthPlugin m
oauth2Bitbucket = oauth2BitbucketScoped defaultScopes
oauth2BitbucketScoped :: YesodAuth m => [Text] -> Text -> Text -> AuthPlugin m
oauth2BitbucketScoped scopes clientId clientSecret =
authOAuth2 pluginName oauth2 $ \manager token -> do
(User userId, userResponse) <- authGetProfile
pluginName
manager
token
"https://api.bitbucket.com/2.0/user"
pure Creds
{ credsPlugin = pluginName
, credsIdent = T.pack $ show userId
, credsExtra = setExtra token userResponse
}
where
oauth2 = OAuth2
{ oauthClientId = clientId
, oauthClientSecret = Just clientSecret
, oauthOAuthorizeEndpoint =
"https://bitbucket.com/site/oauth2/authorize"
`withQuery` [scopeParam "," scopes]
, oauthAccessTokenEndpoint =
"https://bitbucket.com/site/oauth2/access_token"
, oauthCallback = Nothing
}