{-# LANGUAGE OverloadedStrings #-}
module Yesod.Auth.OAuth2.ORCID
( oauth2ORCID
) where
import qualified Data.Text as T
import Yesod.Auth.OAuth2.Prelude
pluginName :: Text
pluginName :: Text
pluginName = Text
"orcid"
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
"sub"
oauth2ORCID
:: YesodAuth m
=> Text
-> Text
-> AuthPlugin m
oauth2ORCID :: forall m. YesodAuth m => Text -> Text -> AuthPlugin m
oauth2ORCID 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://orcid.org/oauth/userinfo"
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 = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Text -> String
forall a. Show a => a -> String
show 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 =
URI
"https://orcid.org/oauth/authorize"
URI -> [(ByteString, ByteString)] -> URI
forall a. URIRef a -> [(ByteString, ByteString)] -> URIRef a
`withQuery` [Text -> [Text] -> (ByteString, ByteString)
scopeParam Text
" " [Text
"openid"]]
, oauth2TokenEndpoint :: URI
oauth2TokenEndpoint = URI
"https://orcid.org/oauth/token"
, oauth2RedirectUri :: Maybe URI
oauth2RedirectUri = Maybe URI
forall a. Maybe a
Nothing
}