Add custom widget functions to Azure AD v2

This commit is contained in:
jaanisfehling 2024-11-04 20:08:22 +01:00 committed by GitHub
parent 50cc0ea49b
commit 51c6574183
No known key found for this signature in database
GPG Key ID: B5690EEEBB952194

View File

@ -1,4 +1,5 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
-- | -- |
-- --
@ -9,9 +10,12 @@
module Yesod.Auth.OAuth2.AzureADv2 module Yesod.Auth.OAuth2.AzureADv2
( oauth2AzureADv2 ( oauth2AzureADv2
, oauth2AzureADv2Scoped , oauth2AzureADv2Scoped
, oauth2AzureADv2Widget
, oauth2AzureADv2ScopedWidget
) where ) where
import Yesod.Auth.OAuth2.Prelude import Yesod.Auth.OAuth2.Prelude
import Yesod.Core (WidgetFor, whamlet)
import Prelude import Prelude
import Data.String import Data.String
@ -41,9 +45,21 @@ oauth2AzureADv2
-> AuthPlugin m -> AuthPlugin m
oauth2AzureADv2 = oauth2AzureADv2Scoped defaultScopes oauth2AzureADv2 = oauth2AzureADv2Scoped defaultScopes
oauth2AzureADv2Widget
:: YesodAuth m => WidgetFor m () -> Text -> Text -> Text -> AuthPlugin m
oauth2AzureADv2Widget widget =
oauth2AzureADv2ScopedWidget widget defaultScopes
oauth2AzureADv2Scoped oauth2AzureADv2Scoped
:: YesodAuth m => [Text] -> Text -> Text -> Text -> AuthPlugin m
oauth2AzureADv2Scoped =
oauth2AzureADv2ScopedWidget [whamlet|Login via #{pluginName}|]
oauth2AzureADv2ScopedWidget
:: YesodAuth m :: YesodAuth m
=> [Text] => WidgetFor m ()
-- ^ Widget
-> [Text]
-- ^ Scopes -- ^ Scopes
-> Text -> Text
-- ^ Tenant Id -- ^ Tenant Id
@ -54,8 +70,8 @@ oauth2AzureADv2Scoped
-> Text -> Text
-- ^ Client Secret -- ^ Client Secret
-> AuthPlugin m -> AuthPlugin m
oauth2AzureADv2Scoped scopes tenantId clientId clientSecret = oauth2AzureADv2ScopedWidget widget scopes tenantId clientId clientSecret =
authOAuth2 pluginName oauth2 $ \manager token -> do authOAuth2Widget widget pluginName oauth2 $ \manager token -> do
(User userId, userResponse) <- (User userId, userResponse) <-
authGetProfile authGetProfile
pluginName pluginName