{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE QuasiQuotes #-} -- | -- -- OAuth2 plugin for http://eveonline.com -- -- * Authenticates against eveonline -- * Uses EVEs unique account-user-char-hash as credentials identifier -- module Yesod.Auth.OAuth2.EveOnline ( oauth2Eve , oauth2EveScoped , WidgetType(..) ) where import Yesod.Auth.OAuth2.Prelude import qualified Data.Text as T import Yesod.Core.Widget newtype User = User Text instance FromJSON User where parseJSON = withObject "User" $ \o -> User <$> o .: "CharacterOwnerHash" data WidgetType m = Plain -- ^ Simple "Login via eveonline" text | BigWhite | SmallWhite | BigBlack | SmallBlack | Custom (WidgetT m IO ()) asWidget :: YesodAuth m => WidgetType m -> WidgetT m IO () asWidget Plain = [whamlet|Login via eveonline|] asWidget BigWhite = [whamlet||] asWidget BigBlack = [whamlet||] asWidget SmallWhite = [whamlet||] asWidget SmallBlack = [whamlet||] asWidget (Custom a) = a pluginName :: Text pluginName = "eveonline" defaultScopes :: [Text] defaultScopes = ["publicData"] oauth2Eve :: YesodAuth m => WidgetType m -> Text -> Text -> AuthPlugin m oauth2Eve = oauth2EveScoped defaultScopes oauth2EveScoped :: YesodAuth m => [Text] -> WidgetType m -> Text -> Text -> AuthPlugin m oauth2EveScoped scopes widgetType clientId clientSecret = authOAuth2Widget (asWidget widgetType) pluginName oauth2 $ \manager token -> do (User userId, userResponse) <- authGetProfile pluginName manager token "https://login.eveonline.com/oauth/verify" pure Creds { credsPlugin = "eveonline" -- FIXME: Preserved bug. See similar comment in Bitbucket provider. , credsIdent = T.pack $ show userId , credsExtra = setExtra token userResponse } where oauth2 = OAuth2 { oauthClientId = clientId , oauthClientSecret = clientSecret , oauthOAuthorizeEndpoint = "https://login.eveonline.com/oauth/authorize" `withQuery` [ ("response_type", "code") , scopeParam " " scopes ] , oauthAccessTokenEndpoint = "https://login.eveonline.com/oauth/token" , oauthCallback = Nothing }