yesod-auth-oauth2/Yesod/Auth/OAuth2/Salesforce.hs
patrick brisbin 937ad572a3 Update to LTS-9.5 and hoauth2 1.3.0
The largest changes were around the hoauth2 interface:

The OAuth2 type replaced all of its ByteString fields with either Text
or URI. This is a huge improvement. The fields that are now Text are the
type we had them in anyway. The fields that are now URI are type safe
and easier to manipulate. For example, we were doing very unsafe query
string manipulations looking for raw ? or & values, but now we can work
with tuples in a well-typed property.

Additionally the AccessToken type was upgraded to OAuth2Token with an
accessToken field, and the simple Either ByteString a results were
replaced by a real OAuth2Error type. This required changes to our
InvalidProfileResponse mechanism to support.

To make working with uri-bytestring more convenient, an Extension
library was added with some useful instances and helper functions. This
library may be upstreamed at some point.
2017-10-18 17:21:47 -04:00

155 lines
5.3 KiB
Haskell

{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
-- |
--
-- OAuth2 plugin for http://login.salesforce.com
--
-- * Authenticates against Salesforce
-- * Uses Salesforce user id as credentials identifier
-- * Returns given_name, family_name, email and avatar_url as extras
--
module Yesod.Auth.OAuth2.Salesforce
( oauth2Salesforce
, oauth2SalesforceScoped
, oauth2SalesforceSandbox
, oauth2SalesforceSandboxScoped
, module Yesod.Auth.OAuth2
) where
#if __GLASGOW_HASKELL__ < 710
import Control.Applicative ((<$>), (<*>))
#endif
import Control.Exception.Lifted
import Control.Monad (mzero)
import Data.Aeson
import Data.Text (Text)
import Network.HTTP.Conduit (Manager)
import Yesod.Auth
import Yesod.Auth.OAuth2
import qualified Data.Text as T
oauth2Salesforce :: YesodAuth m
=> Text -- ^ Client ID
-> Text -- ^ Client Secret
-> AuthPlugin m
oauth2Salesforce = oauth2SalesforceScoped ["openid", "email", "api"]
svcName :: Text
svcName = "salesforce"
oauth2SalesforceScoped :: YesodAuth m
=> [Text] -- ^ List of scopes to request
-> Text -- ^ Client ID
-> Text -- ^ Client Secret
-> AuthPlugin m
oauth2SalesforceScoped scopes clientId clientSecret =
authOAuth2 svcName oauth fetchSalesforceUser
where
oauth = OAuth2
{ oauthClientId = clientId
, oauthClientSecret = clientSecret
, oauthOAuthorizeEndpoint = "https://login.salesforce.com/services/oauth2/authorize" `withQuery`
[ scopeParam " " scopes
]
, oauthAccessTokenEndpoint = "https://login.salesforce.com/services/oauth2/token"
, oauthCallback = Nothing
}
fetchSalesforceUser :: Manager -> OAuth2Token -> IO (Creds m)
fetchSalesforceUser manager token = do
result <- authGetJSON manager (accessToken token) "https://login.salesforce.com/services/oauth2/userinfo"
case result of
Right user -> return $ toCreds svcName user token
Left err -> throwIO $ invalidProfileResponse svcName err
svcNameSb :: Text
svcNameSb = "salesforce-sandbox"
oauth2SalesforceSandbox :: YesodAuth m
=> Text -- ^ Client ID
-> Text -- ^ Client Secret
-> AuthPlugin m
oauth2SalesforceSandbox = oauth2SalesforceSandboxScoped ["openid", "email"]
oauth2SalesforceSandboxScoped :: YesodAuth m
=> [Text] -- ^ List of scopes to request
-> Text -- ^ Client ID
-> Text -- ^ Client Secret
-> AuthPlugin m
oauth2SalesforceSandboxScoped scopes clientId clientSecret =
authOAuth2 svcNameSb oauth fetchSalesforceSandboxUser
where
oauth = OAuth2
{ oauthClientId = clientId
, oauthClientSecret = clientSecret
, oauthOAuthorizeEndpoint = "https://test.salesforce.com/services/oauth2/authorize" `withQuery`
[ scopeParam " " scopes
]
, oauthAccessTokenEndpoint = "https://test.salesforce.com/services/oauth2/token"
, oauthCallback = Nothing
}
fetchSalesforceSandboxUser :: Manager -> OAuth2Token -> IO (Creds m)
fetchSalesforceSandboxUser manager token = do
result <- authGetJSON manager (accessToken token) $ "https://test.salesforce.com/services/oauth2/userinfo"
case result of
Right user -> return $ toCreds svcNameSb user token
Left err -> throwIO $ invalidProfileResponse svcNameSb err
data User = User
{ userId :: Text
, userOrg :: Text
, userNickname :: Text
, userName :: Text
, userGivenName :: Text
, userFamilyName :: Text
, userTimeZone :: Text
, userEmail :: Text
, userPicture :: Text
, userPhone :: Maybe Text
, userRestUrl :: Text
}
instance FromJSON User where
parseJSON (Object o) = do
userId <- o .: "user_id"
userOrg <- o .: "organization_id"
userNickname <- o .: "nickname"
userName <- o .: "name"
userGivenName <- o .: "given_name"
userFamilyName <- o .: "family_name"
userTimeZone <- o .: "zoneinfo"
userEmail <- o .: "email"
userPicture <- o .: "picture"
userPhone <- o .:? "phone_number"
urls <- o .: "urls"
userRestUrl <- urls .: "rest"
return User{..}
parseJSON _ = mzero
toCreds :: Text -> User -> OAuth2Token -> Creds m
toCreds name user token = Creds
{ credsPlugin = name
, credsIdent = userId user
, credsExtra =
[ ("email", userEmail user)
, ("org", userOrg user)
, ("nickname", userName user)
, ("name", userName user)
, ("given_name", userGivenName user)
, ("family_name", userFamilyName user)
, ("time_zone", userTimeZone user)
, ("avatar_url", userPicture user)
, ("rest_url", userRestUrl user)
, ("access_token", atoken $ accessToken token)
]
++ maybeExtra "refresh_token" (rtoken <$> refreshToken token)
++ maybeExtra "expires_in" ((T.pack . show) <$> expiresIn token)
++ maybeExtra "phone_number" (userPhone user)
}