{-# LANGUAGE QuasiQuotes #-}

-- | [Auth0](https://auth0.com)
--
--   * [Auth0 Authorize Application](https://auth0.com/docs/api/authentication#authorize-application)
--
--   * [OAuth 2.0 Authorization Framework](https://auth0.com/docs/authenticate/protocols/oauth)
module Network.OAuth2.Provider.Auth0 where

import Control.Monad.IO.Class (MonadIO (..))
import Control.Monad.Trans.Except (ExceptT (..))
import Data.Aeson (FromJSON)
import Data.ByteString.Lazy.Char8 qualified as BSL
import Data.Map.Strict qualified as Map
import Data.Set qualified as Set
import Data.Text.Lazy (Text)
import GHC.Generics
import Network.HTTP.Conduit
import Network.OAuth.OAuth2
import Network.OAuth2.Experiment
import Network.OAuth2.Provider
import Network.OIDC.WellKnown
import URI.ByteString.QQ

sampleAuth0AuthorizationCodeApp :: AuthorizationCodeApplication
sampleAuth0AuthorizationCodeApp :: AuthorizationCodeApplication
sampleAuth0AuthorizationCodeApp =
  AuthorizationCodeApplication
    { acClientId :: ClientId
acClientId = ClientId
""
    , acClientSecret :: ClientSecret
acClientSecret = ClientSecret
""
    , acScope :: Set Scope
acScope = [Scope] -> Set Scope
forall a. Ord a => [a] -> Set a
Set.fromList [Scope
"openid", Scope
"profile", Scope
"email", Scope
"offline_access"]
    , acAuthorizeState :: AuthorizeState
acAuthorizeState = AuthorizeState
"CHANGE_ME"
    , acRedirectUri :: URI
acRedirectUri = [uri|http://localhost|]
    , acName :: Text
acName = Text
"sample-auth0-authorization-code-app"
    , acAuthorizeRequestExtraParams :: Map Text Text
acAuthorizeRequestExtraParams = Map Text Text
forall k a. Map k a
Map.empty
    , acTokenRequestAuthenticationMethod :: ClientAuthenticationMethod
acTokenRequestAuthenticationMethod = ClientAuthenticationMethod
ClientSecretBasic
    }

fetchUserInfo ::
  (MonadIO m, HasUserInfoRequest a, FromJSON b) =>
  IdpApplication i a ->
  Manager ->
  AccessToken ->
  ExceptT BSL.ByteString m b
fetchUserInfo :: forall {k} (m :: * -> *) a b (i :: k).
(MonadIO m, HasUserInfoRequest a, FromJSON b) =>
IdpApplication i a
-> Manager -> AccessToken -> ExceptT ByteString m b
fetchUserInfo = IdpApplication i a
-> Manager -> AccessToken -> ExceptT ByteString m b
forall {k} (m :: * -> *) a b (i :: k).
(MonadIO m, HasUserInfoRequest a, FromJSON b) =>
IdpApplication i a
-> Manager -> AccessToken -> ExceptT ByteString m b
conduitUserInfoRequest

mkAuth0Idp ::
  MonadIO m =>
  -- | Full domain with no http protocol. e.g. @foo.auth0.com@
  Text ->
  ExceptT Text m (Idp Auth0)
mkAuth0Idp :: forall (m :: * -> *).
MonadIO m =>
Text -> ExceptT Text m (Idp 'Auth0)
mkAuth0Idp Text
domain = do
  OpenIDConfiguration {URI
issuer :: URI
authorizationEndpoint :: URI
tokenEndpoint :: URI
userinfoEndpoint :: URI
jwksUri :: URI
deviceAuthorizationEndpoint :: URI
issuer :: OpenIDConfiguration -> URI
authorizationEndpoint :: OpenIDConfiguration -> URI
tokenEndpoint :: OpenIDConfiguration -> URI
userinfoEndpoint :: OpenIDConfiguration -> URI
jwksUri :: OpenIDConfiguration -> URI
deviceAuthorizationEndpoint :: OpenIDConfiguration -> URI
..} <- Text -> ExceptT Text m OpenIDConfiguration
forall (m :: * -> *).
MonadIO m =>
Text -> ExceptT Text m OpenIDConfiguration
fetchWellKnown Text
domain
  Idp 'Auth0 -> ExceptT Text m (Idp 'Auth0)
forall a. a -> ExceptT Text m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
    ( Idp
        { --  https://auth0.com/docs/api/authentication#user-profile
          idpUserInfoEndpoint :: URI
idpUserInfoEndpoint = URI
userinfoEndpoint
        , -- https://auth0.com/docs/api/authentication#authorization-code-flow
          idpAuthorizeEndpoint :: URI
idpAuthorizeEndpoint = URI
authorizationEndpoint
        , -- https://auth0.com/docs/api/authentication#authorization-code-flow44
          idpTokenEndpoint :: URI
idpTokenEndpoint = URI
tokenEndpoint
        , idpDeviceAuthorizationEndpoint :: Maybe URI
idpDeviceAuthorizationEndpoint = URI -> Maybe URI
forall a. a -> Maybe a
Just URI
deviceAuthorizationEndpoint
        }
    )

-- | https://auth0.com/docs/api/authentication#user-profile
data Auth0User = Auth0User
  { Auth0User -> Text
name :: Text
  , Auth0User -> Text
email :: Text
  , Auth0User -> Text
sub :: Text
  }
  deriving (Int -> Auth0User -> ShowS
[Auth0User] -> ShowS
Auth0User -> String
(Int -> Auth0User -> ShowS)
-> (Auth0User -> String)
-> ([Auth0User] -> ShowS)
-> Show Auth0User
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Auth0User -> ShowS
showsPrec :: Int -> Auth0User -> ShowS
$cshow :: Auth0User -> String
show :: Auth0User -> String
$cshowList :: [Auth0User] -> ShowS
showList :: [Auth0User] -> ShowS
Show, (forall x. Auth0User -> Rep Auth0User x)
-> (forall x. Rep Auth0User x -> Auth0User) -> Generic Auth0User
forall x. Rep Auth0User x -> Auth0User
forall x. Auth0User -> Rep Auth0User x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Auth0User -> Rep Auth0User x
from :: forall x. Auth0User -> Rep Auth0User x
$cto :: forall x. Rep Auth0User x -> Auth0User
to :: forall x. Rep Auth0User x -> Auth0User
Generic)

instance FromJSON Auth0User