{-# LANGUAGE OverloadedStrings #-}
-- |
-- OAuth2 plugin for <https://auth0.com>
--
-- * Authenticates against specific auth0 tenant
-- * Uses Auth0 user id (a.k.a [sub](https://auth0.com/docs/api/authentication#get-user-info)) as credentials identifier
--
module Yesod.Auth.OAuth2.Auth0
  ( oauth2Auth0HostScopes
  , oauth2Auth0Host
  , defaultAuth0Scopes
  ) where

import Data.Aeson as Aeson
import qualified Data.Text as T
import Prelude
import Yesod.Auth.OAuth2.Prelude

-- | https://auth0.com/docs/api/authentication#get-user-info
newtype User = User T.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 -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"sub"

-- | https://auth0.com/docs/get-started/apis/scopes/openid-connect-scopes#standard-claims
defaultAuth0Scopes :: [Text]
defaultAuth0Scopes :: [Text]
defaultAuth0Scopes = [Text
"openid"]

pluginName :: Text
pluginName :: Text
pluginName = Text
"auth0"

oauth2Auth0Host :: YesodAuth m => URI -> Text -> Text -> AuthPlugin m
oauth2Auth0Host :: URI -> Text -> Text -> AuthPlugin m
oauth2Auth0Host URI
host = URI -> [Text] -> Text -> Text -> AuthPlugin m
forall m.
YesodAuth m =>
URI -> [Text] -> Text -> Text -> AuthPlugin m
oauth2Auth0HostScopes URI
host [Text]
defaultAuth0Scopes

oauth2Auth0HostScopes
  :: YesodAuth m => URI -> [Text] -> Text -> Text -> AuthPlugin m
oauth2Auth0HostScopes :: URI -> [Text] -> Text -> Text -> AuthPlugin m
oauth2Auth0HostScopes URI
host [Text]
scopes Text
clientId Text
clientSecret =
  Text -> OAuth2 -> FetchCreds m -> AuthPlugin m
forall m.
YesodAuth m =>
Text -> OAuth2 -> FetchCreds m -> AuthPlugin m
authOAuth2 Text
pluginName OAuth2
oauth2 (FetchCreds m -> AuthPlugin m) -> FetchCreds m -> AuthPlugin m
forall a b. (a -> b) -> a -> b
$ \Manager
manager OAuth2Token
token -> do
    (User Text
uid, ByteString
userResponse) <- Text -> Manager -> OAuth2Token -> URI -> IO (User, ByteString)
forall a.
FromJSON a =>
Text -> Manager -> OAuth2Token -> URI -> IO (a, ByteString)
authGetProfile Text
pluginName
                                               Manager
manager
                                               OAuth2Token
token
                                               (URI
host URI -> ByteString -> URI
forall a. URIRef a -> ByteString -> URIRef a
`withPath` ByteString
"/userinfo")
    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
uid
               , 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
    { oauth2ClientId :: Text
oauth2ClientId          = Text
clientId
    , oauth2ClientSecret :: Maybe Text
oauth2ClientSecret      = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
clientSecret
    , oauth2AuthorizeEndpoint :: URI
oauth2AuthorizeEndpoint = URI
host
                                URI -> ByteString -> URI
forall a. URIRef a -> ByteString -> URIRef a
`withPath`  ByteString
"/authorize"
                                URI -> [(ByteString, ByteString)] -> URI
forall a. URIRef a -> [(ByteString, ByteString)] -> URIRef a
`withQuery` [Text -> [Text] -> (ByteString, ByteString)
scopeParam Text
" " [Text]
scopes]
    , oauth2TokenEndpoint :: URI
oauth2TokenEndpoint     = URI
host URI -> ByteString -> URI
forall a. URIRef a -> ByteString -> URIRef a
`withPath` ByteString
"/oauth/token"
    , oauth2RedirectUri :: Maybe URI
oauth2RedirectUri       = Maybe URI
forall a. Maybe a
Nothing
    }