{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE TypeFamilies #-} module Network.OAuth2.Provider.Linkedin where import Data.Aeson import Data.Map.Strict qualified as Map import Data.Set qualified as Set import Data.Text.Lazy (Text) import GHC.Generics import Network.OAuth.OAuth2 import Network.OAuth2.Experiment import URI.ByteString.QQ data Linkedin = Linkedin deriving (Linkedin -> Linkedin -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Linkedin -> Linkedin -> Bool $c/= :: Linkedin -> Linkedin -> Bool == :: Linkedin -> Linkedin -> Bool $c== :: Linkedin -> Linkedin -> Bool Eq, Int -> Linkedin -> ShowS [Linkedin] -> ShowS Linkedin -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Linkedin] -> ShowS $cshowList :: [Linkedin] -> ShowS show :: Linkedin -> String $cshow :: Linkedin -> String showsPrec :: Int -> Linkedin -> ShowS $cshowsPrec :: Int -> Linkedin -> ShowS Show) type instance IdpUserInfo Linkedin = LinkedinUser defaultLinkedinApp :: IdpApplication 'AuthorizationCode Linkedin defaultLinkedinApp :: IdpApplication 'AuthorizationCode Linkedin defaultLinkedinApp = AuthorizationCodeIdpApplication { $sel:idpAppClientId:AuthorizationCodeIdpApplication :: ClientId idpAppClientId = ClientId "" , $sel:idpAppClientSecret:AuthorizationCodeIdpApplication :: ClientSecret idpAppClientSecret = ClientSecret "" , $sel:idpAppScope:AuthorizationCodeIdpApplication :: Set Scope idpAppScope = forall a. Ord a => [a] -> Set a Set.fromList [Scope "r_liteprofile"] , $sel:idpAppAuthorizeState:AuthorizationCodeIdpApplication :: AuthorizeState idpAppAuthorizeState = AuthorizeState "CHANGE_ME" , $sel:idpAppAuthorizeExtraParams:AuthorizationCodeIdpApplication :: Map Text Text idpAppAuthorizeExtraParams = forall k a. Map k a Map.empty , $sel:idpAppRedirectUri:AuthorizationCodeIdpApplication :: URI idpAppRedirectUri = [uri|http://localhost|] , $sel:idpAppName:AuthorizationCodeIdpApplication :: Text idpAppName = Text "default-linkedin-App" , $sel:idpAppTokenRequestAuthenticationMethod:AuthorizationCodeIdpApplication :: ClientAuthenticationMethod idpAppTokenRequestAuthenticationMethod = ClientAuthenticationMethod ClientSecretPost , $sel:idp:AuthorizationCodeIdpApplication :: Idp Linkedin idp = Idp Linkedin defaultLinkedinIdp } defaultLinkedinIdp :: Idp Linkedin defaultLinkedinIdp :: Idp Linkedin defaultLinkedinIdp = Idp { $sel:idpFetchUserInfo:Idp :: forall (m :: * -> *). (FromJSON (IdpUserInfo Linkedin), MonadIO m) => Manager -> AccessToken -> URI -> ExceptT ByteString m (IdpUserInfo Linkedin) idpFetchUserInfo = forall a (m :: * -> *). (FromJSON a, MonadIO m) => Manager -> AccessToken -> URI -> ExceptT ByteString m a authGetJSON @(IdpUserInfo Linkedin) , $sel:idpUserInfoEndpoint:Idp :: URI idpUserInfoEndpoint = [uri|https://api.linkedin.com/v2/me|] , $sel:idpAuthorizeEndpoint:Idp :: URI idpAuthorizeEndpoint = [uri|https://www.linkedin.com/oauth/v2/authorization|] , $sel:idpTokenEndpoint:Idp :: URI idpTokenEndpoint = [uri|https://www.linkedin.com/oauth/v2/accessToken|] } data LinkedinUser = LinkedinUser { LinkedinUser -> Text localizedFirstName :: Text , LinkedinUser -> Text localizedLastName :: Text } deriving (Int -> LinkedinUser -> ShowS [LinkedinUser] -> ShowS LinkedinUser -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [LinkedinUser] -> ShowS $cshowList :: [LinkedinUser] -> ShowS show :: LinkedinUser -> String $cshow :: LinkedinUser -> String showsPrec :: Int -> LinkedinUser -> ShowS $cshowsPrec :: Int -> LinkedinUser -> ShowS Show, forall x. Rep LinkedinUser x -> LinkedinUser forall x. LinkedinUser -> Rep LinkedinUser x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep LinkedinUser x -> LinkedinUser $cfrom :: forall x. LinkedinUser -> Rep LinkedinUser x Generic, LinkedinUser -> LinkedinUser -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: LinkedinUser -> LinkedinUser -> Bool $c/= :: LinkedinUser -> LinkedinUser -> Bool == :: LinkedinUser -> LinkedinUser -> Bool $c== :: LinkedinUser -> LinkedinUser -> Bool Eq) instance FromJSON LinkedinUser