{-# LANGUAGE OverloadedStrings #-}

-- |
--
-- OAuth2 plugin for Azure AD using the new v2 endpoints.
--
-- * Authenticates against Azure AD
-- * Uses email as credentials identifier
module Yesod.Auth.OAuth2.AzureADv2
  ( oauth2AzureADv2
  , oauth2AzureADv2Scoped
  ) where

import Yesod.Auth.OAuth2.Prelude
import Prelude

import Data.String
import Data.Text (unpack)

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 -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"mail"

pluginName :: Text
pluginName :: Text
pluginName = Text
"azureadv2"

defaultScopes :: [Text]
defaultScopes :: [Text]
defaultScopes = [Text
"openid", Text
"profile"]

oauth2AzureADv2
  :: YesodAuth m
  => Text
  -- ^ Tenant Id
  --
  -- If using a multi-tenant App, @common@ can be given here.
  -> Text
  -- ^ Client Id
  -> Text
  -- ^ Client secret
  -> AuthPlugin m
oauth2AzureADv2 :: forall m. YesodAuth m => Text -> Text -> Text -> AuthPlugin m
oauth2AzureADv2 = [Text] -> Text -> Text -> Text -> AuthPlugin m
forall m.
YesodAuth m =>
[Text] -> Text -> Text -> Text -> AuthPlugin m
oauth2AzureADv2Scoped [Text]
defaultScopes

oauth2AzureADv2Scoped
  :: YesodAuth m
  => [Text]
  -- ^ Scopes
  -> Text
  -- ^ Tenant Id
  --
  -- If using a multi-tenant App, @common@ can be given here.
  -> Text
  -- ^ Client Id
  -> Text
  -- ^ Client Secret
  -> AuthPlugin m
oauth2AzureADv2Scoped :: forall m.
YesodAuth m =>
[Text] -> Text -> Text -> Text -> AuthPlugin m
oauth2AzureADv2Scoped [Text]
scopes Text
tenantId 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
userId, 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
"https://graph.microsoft.com/v1.0/me"

    Creds m -> IO (Creds m)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
      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
      { oauth2ClientId :: Text
oauth2ClientId = Text
clientId
      , oauth2ClientSecret :: Maybe Text
oauth2ClientSecret = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
clientSecret
      , oauth2AuthorizeEndpoint :: URI
oauth2AuthorizeEndpoint =
          String -> URI
forall {a}. IsString a => String -> a
tenantUrl String
"/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 = String -> URI
forall {a}. IsString a => String -> a
tenantUrl String
"/token"
      , oauth2RedirectUri :: Maybe URI
oauth2RedirectUri = Maybe URI
forall a. Maybe a
Nothing
      }

  tenantUrl :: String -> a
tenantUrl String
path =
    String -> a
forall {a}. IsString a => String -> a
fromString (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$
      String
"https://login.microsoftonline.com/"
        String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Text -> String
unpack Text
tenantId
        String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"/oauth2/v2.0"
        String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
path