{-# LANGUAGE OverloadedStrings #-}
-- |
--
-- OAuth2 plugin for http://login.salesforce.com
--
-- * Authenticates against Salesforce (or sandbox)
-- * Uses Salesforce user id as credentials identifier
--
module Yesod.Auth.OAuth2.Salesforce
    ( oauth2Salesforce
    , oauth2SalesforceScoped
    , oauth2SalesforceSandbox
    , oauth2SalesforceSandboxScoped
    )
where

import Yesod.Auth.OAuth2.Prelude

newtype User = User Text

instance FromJSON User where
    parseJSON :: Value -> Parser User
parseJSON = String -> (Object -> Parser User) -> Value -> Parser User
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"User" ((Object -> Parser User) -> Value -> Parser User)
-> (Object -> Parser User) -> Value -> Parser User
forall a b. (a -> b) -> a -> b
$ \Object
o -> Text -> User
User (Text -> User) -> Parser Text -> Parser User
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"user_id"

pluginName :: Text
pluginName :: Text
pluginName = Text
"salesforce"

defaultScopes :: [Text]
defaultScopes :: [Text]
defaultScopes = [Text
"openid", Text
"email", Text
"api"]

oauth2Salesforce :: YesodAuth m => Text -> Text -> AuthPlugin m
oauth2Salesforce :: Text -> Text -> AuthPlugin m
oauth2Salesforce = [Text] -> Text -> Text -> AuthPlugin m
forall m. YesodAuth m => [Text] -> Text -> Text -> AuthPlugin m
oauth2SalesforceScoped [Text]
defaultScopes

oauth2SalesforceScoped :: YesodAuth m => [Text] -> Text -> Text -> AuthPlugin m
oauth2SalesforceScoped :: [Text] -> Text -> Text -> AuthPlugin m
oauth2SalesforceScoped = Text -> URI -> URI -> URI -> [Text] -> Text -> Text -> AuthPlugin m
forall m.
YesodAuth m =>
Text -> URI -> URI -> URI -> [Text] -> Text -> Text -> AuthPlugin m
salesforceHelper
    Text
pluginName
    URI
"https://login.salesforce.com/services/oauth2/userinfo"
    URI
"https://login.salesforce.com/services/oauth2/authorize"
    URI
"https://login.salesforce.com/services/oauth2/token"

oauth2SalesforceSandbox :: YesodAuth m => Text -> Text -> AuthPlugin m
oauth2SalesforceSandbox :: Text -> Text -> AuthPlugin m
oauth2SalesforceSandbox = [Text] -> Text -> Text -> AuthPlugin m
forall m. YesodAuth m => [Text] -> Text -> Text -> AuthPlugin m
oauth2SalesforceSandboxScoped [Text]
defaultScopes

oauth2SalesforceSandboxScoped
    :: YesodAuth m => [Text] -> Text -> Text -> AuthPlugin m
oauth2SalesforceSandboxScoped :: [Text] -> Text -> Text -> AuthPlugin m
oauth2SalesforceSandboxScoped = Text -> URI -> URI -> URI -> [Text] -> Text -> Text -> AuthPlugin m
forall m.
YesodAuth m =>
Text -> URI -> URI -> URI -> [Text] -> Text -> Text -> AuthPlugin m
salesforceHelper
    (Text
pluginName Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"-sandbox")
    URI
"https://test.salesforce.com/services/oauth2/userinfo"
    URI
"https://test.salesforce.com/services/oauth2/authorize"
    URI
"https://test.salesforce.com/services/oauth2/token"

salesforceHelper
    :: YesodAuth m
    => Text
    -> URI -- ^ User profile
    -> URI -- ^ Authorize
    -> URI -- ^ Token
    -> [Text]
    -> Text
    -> Text
    -> AuthPlugin m
salesforceHelper :: Text -> URI -> URI -> URI -> [Text] -> Text -> Text -> AuthPlugin m
salesforceHelper Text
name URI
profileUri URI
authorizeUri URI
tokenUri [Text]
scopes Text
clientId Text
clientSecret
    = Text -> OAuth2 -> FetchCreds m -> AuthPlugin m
forall m.
YesodAuth m =>
Text -> OAuth2 -> FetchCreds m -> AuthPlugin m
authOAuth2 Text
name OAuth2
oauth2 (FetchCreds m -> AuthPlugin m) -> FetchCreds m -> AuthPlugin m
forall a b. (a -> b) -> a -> b
$ \Manager
manager OAuth2Token
token -> do
        (User Text
userId, ByteString
userResponse) <- Text -> Manager -> OAuth2Token -> URI -> IO (User, ByteString)
forall a.
FromJSON a =>
Text -> Manager -> OAuth2Token -> URI -> IO (a, ByteString)
authGetProfile
            Text
name
            Manager
manager
            OAuth2Token
token
            URI
profileUri

        Creds m -> IO (Creds m)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Creds :: forall master. Text -> Text -> [(Text, Text)] -> Creds master
Creds
            { credsPlugin :: Text
credsPlugin = Text
pluginName
            , credsIdent :: Text
credsIdent = Text
userId
            , credsExtra :: [(Text, Text)]
credsExtra = OAuth2Token -> ByteString -> [(Text, Text)]
setExtra OAuth2Token
token ByteString
userResponse
            }
  where
    oauth2 :: OAuth2
oauth2 = OAuth2 :: Text -> Maybe Text -> URI -> URI -> Maybe URI -> OAuth2
OAuth2
        { oauthClientId :: Text
oauthClientId = Text
clientId
        , oauthClientSecret :: Maybe Text
oauthClientSecret = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
clientSecret
        , oauthOAuthorizeEndpoint :: URI
oauthOAuthorizeEndpoint =
            URI
authorizeUri URI -> [(ByteString, ByteString)] -> URI
forall a. URIRef a -> [(ByteString, ByteString)] -> URIRef a
`withQuery` [Text -> [Text] -> (ByteString, ByteString)
scopeParam Text
" " [Text]
scopes]
        , oauthAccessTokenEndpoint :: URI
oauthAccessTokenEndpoint = URI
tokenUri
        , oauthCallback :: Maybe URI
oauthCallback = Maybe URI
forall a. Maybe a
Nothing
        }