{-# 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 :: 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 -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"CharacterOwnerHash"

data WidgetType m
    = Plain -- ^ Simple "Login via eveonline" text
    | BigWhite
    | SmallWhite
    | BigBlack
    | SmallBlack
    | Custom (WidgetFor m ())

asWidget :: YesodAuth m => WidgetType m -> WidgetFor m ()
asWidget :: WidgetType m -> WidgetFor m ()
asWidget WidgetType m
Plain = [whamlet|Login via eveonline|]
asWidget WidgetType m
BigWhite =
    [whamlet|<img src="https://images.contentful.com/idjq7aai9ylm/4PTzeiAshqiM8osU2giO0Y/5cc4cb60bac52422da2e45db87b6819c/EVE_SSO_Login_Buttons_Large_White.png?w=270&h=45">|]
asWidget WidgetType m
BigBlack
    = [whamlet|<img src="https://images.contentful.com/idjq7aai9ylm/4fSjj56uD6CYwYyus4KmES/4f6385c91e6de56274d99496e6adebab/EVE_SSO_Login_Buttons_Large_Black.png?w=270&h=45">|]
asWidget WidgetType m
SmallWhite
    = [whamlet|<img src="https://images.contentful.com/idjq7aai9ylm/18BxKSXCymyqY4QKo8KwKe/c2bdded6118472dd587c8107f24104d7/EVE_SSO_Login_Buttons_Small_White.png?w=195&h=30">|]
asWidget WidgetType m
SmallBlack
    = [whamlet|<img src="https://images.contentful.com/idjq7aai9ylm/12vrPsIMBQi28QwCGOAqGk/33234da7672c6b0cdca394fc8e0b1c2b/EVE_SSO_Login_Buttons_Small_Black.png?w=195&h=30">|]
asWidget (Custom WidgetFor m ()
a) = WidgetFor m ()
a

pluginName :: Text
pluginName :: Text
pluginName = Text
"eveonline"

defaultScopes :: [Text]
defaultScopes :: [Text]
defaultScopes = [Text
"publicData"]

oauth2Eve :: YesodAuth m => WidgetType m -> Text -> Text -> AuthPlugin m
oauth2Eve :: WidgetType m -> Text -> Text -> AuthPlugin m
oauth2Eve = [Text] -> WidgetType m -> Text -> Text -> AuthPlugin m
forall m.
YesodAuth m =>
[Text] -> WidgetType m -> Text -> Text -> AuthPlugin m
oauth2EveScoped [Text]
defaultScopes

oauth2EveScoped
    :: YesodAuth m => [Text] -> WidgetType m -> Text -> Text -> AuthPlugin m
oauth2EveScoped :: [Text] -> WidgetType m -> Text -> Text -> AuthPlugin m
oauth2EveScoped [Text]
scopes WidgetType m
widgetType Text
clientId Text
clientSecret =
    WidgetFor m () -> Text -> OAuth2 -> FetchCreds m -> AuthPlugin m
forall m.
YesodAuth m =>
WidgetFor m () -> Text -> OAuth2 -> FetchCreds m -> AuthPlugin m
authOAuth2Widget (WidgetType m -> WidgetFor m ()
forall m. YesodAuth m => WidgetType m -> WidgetFor m ()
asWidget WidgetType m
widgetType) 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://login.eveonline.com/oauth/verify"

              Creds m -> IO (Creds m)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Creds :: forall master. Text -> Text -> [(Text, Text)] -> Creds master
Creds
                  { credsPlugin :: Text
credsPlugin = Text
"eveonline"
                  -- FIXME: Preserved bug. See similar comment in Bitbucket provider.
                  , 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 :: Text -> Maybe Text -> URI -> URI -> Maybe URI -> OAuth2
OAuth2
        { oauthClientId :: Text
oauthClientId = Text
clientId
        , oauthClientSecret :: Maybe Text
oauthClientSecret = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
clientSecret
        , oauthOAuthorizeEndpoint :: URI
oauthOAuthorizeEndpoint =
            URI
"https://login.eveonline.com/oauth/authorize"
                URI -> [(ByteString, ByteString)] -> URI
forall a. URIRef a -> [(ByteString, ByteString)] -> URIRef a
`withQuery` [(ByteString
"response_type", ByteString
"code"), Text -> [Text] -> (ByteString, ByteString)
scopeParam Text
" " [Text]
scopes]
        , oauthAccessTokenEndpoint :: URI
oauthAccessTokenEndpoint = URI
"https://login.eveonline.com/oauth/token"
        , oauthCallback :: Maybe URI
oauthCallback = Maybe URI
forall a. Maybe a
Nothing
        }