Skip to content

Commit

Permalink
Add custom widget functions to Azure AD v2
Browse files Browse the repository at this point in the history
  • Loading branch information
jaanisfehling authored Nov 4, 2024
1 parent 50cc0ea commit 51c6574
Showing 1 changed file with 19 additions and 3 deletions.
22 changes: 19 additions & 3 deletions src/Yesod/Auth/OAuth2/AzureADv2.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}

-- |
--
Expand All @@ -9,9 +10,12 @@
module Yesod.Auth.OAuth2.AzureADv2
( oauth2AzureADv2
, oauth2AzureADv2Scoped
, oauth2AzureADv2Widget
, oauth2AzureADv2ScopedWidget
) where

import Yesod.Auth.OAuth2.Prelude
import Yesod.Core (WidgetFor, whamlet)
import Prelude

import Data.String
Expand Down Expand Up @@ -41,9 +45,21 @@ oauth2AzureADv2
-> AuthPlugin m
oauth2AzureADv2 = oauth2AzureADv2Scoped defaultScopes

oauth2AzureADv2Widget
:: YesodAuth m => WidgetFor m () -> Text -> Text -> Text -> AuthPlugin m
oauth2AzureADv2Widget widget =
oauth2AzureADv2ScopedWidget widget defaultScopes

oauth2AzureADv2Scoped
:: YesodAuth m => [Text] -> Text -> Text -> Text -> AuthPlugin m
oauth2AzureADv2Scoped =
oauth2AzureADv2ScopedWidget [whamlet|Login via #{pluginName}|]

oauth2AzureADv2ScopedWidget
:: YesodAuth m
=> [Text]
=> WidgetFor m ()
-- ^ Widget
-> [Text]
-- ^ Scopes
-> Text
-- ^ Tenant Id
Expand All @@ -54,8 +70,8 @@ oauth2AzureADv2Scoped
-> Text
-- ^ Client Secret
-> AuthPlugin m
oauth2AzureADv2Scoped scopes tenantId clientId clientSecret =
authOAuth2 pluginName oauth2 $ \manager token -> do
oauth2AzureADv2ScopedWidget widget scopes tenantId clientId clientSecret =
authOAuth2Widget widget pluginName oauth2 $ \manager token -> do
(User userId, userResponse) <-
authGetProfile
pluginName
Expand Down

0 comments on commit 51c6574

Please sign in to comment.