{-# LANGUAGE OverloadedStrings #-}

-- |
--
-- OAuth2 plugin for Battle.Net
--
-- * Authenticates against battle.net.
-- * Uses user's id as credentials identifier.
-- * Returns user's battletag in extras.
--
module Yesod.Auth.OAuth2.BattleNet
  ( oauth2BattleNet
  , oAuth2BattleNet
  ) where

import Yesod.Auth.OAuth2.Prelude

import qualified Data.Text as T (pack, toLower)
import Yesod.Core.Widget

newtype User = User Int

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 -> Int -> User
User (Int -> User) -> Parser Int -> Parser User
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"

pluginName :: Text
pluginName :: Text
pluginName = Text
"battle.net"

oauth2BattleNet
  :: YesodAuth m
  => WidgetFor m () -- ^ Login widget
  -> Text -- ^ User region (e.g. "eu", "cn", "us")
  -> Text -- ^ Client ID
  -> Text -- ^ Client Secret
  -> AuthPlugin m
oauth2BattleNet :: WidgetFor m () -> Text -> Text -> Text -> AuthPlugin m
oauth2BattleNet WidgetFor m ()
widget Text
region 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 WidgetFor m ()
widget 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 Int
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 -> IO (User, ByteString)) -> URI -> IO (User, ByteString)
forall a b. (a -> b) -> a -> b
$ Scheme -> Host -> RelativeRef -> URI
fromRelative Scheme
"https" (Text -> Host
apiHost (Text -> Host) -> Text -> Host
forall a b. (a -> b) -> a -> b
$ Text -> Text
T.toLower Text
region) RelativeRef
"/account/user"

    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
pluginName
               , credsIdent :: Text
credsIdent  = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Int -> String
forall a. Show a => a -> String
show Int
userId
               , credsExtra :: [(Text, Text)]
credsExtra  = OAuth2Token -> ByteString -> [(Text, Text)]
setExtra OAuth2Token
token ByteString
userResponse
               }
 where
  host :: Host
host   = Text -> Host
wwwHost (Text -> Host) -> Text -> Host
forall a b. (a -> b) -> a -> b
$ Text -> Text
T.toLower Text
region
  oauth2 :: OAuth2
oauth2 = OAuth2 :: Text -> Maybe Text -> URI -> URI -> Maybe URI -> 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 = Scheme -> Host -> RelativeRef -> URI
fromRelative Scheme
"https" Host
host RelativeRef
"/oauth/authorize"
    , oauth2TokenEndpoint :: URI
oauth2TokenEndpoint     = Scheme -> Host -> RelativeRef -> URI
fromRelative Scheme
"https" Host
host RelativeRef
"/oauth/token"
    , oauth2RedirectUri :: Maybe URI
oauth2RedirectUri       = Maybe URI
forall a. Maybe a
Nothing
    }


apiHost :: Text -> Host
apiHost :: Text -> Host
apiHost Text
"cn"   = Host
"api.battlenet.com.cn"
apiHost Text
region = ByteString -> Host
Host (ByteString -> Host) -> ByteString -> Host
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
encodeUtf8 (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ Text
region Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
".api.battle.net"

wwwHost :: Text -> Host
wwwHost :: Text -> Host
wwwHost Text
"cn"   = Host
"www.battlenet.com.cn"
wwwHost Text
region = ByteString -> Host
Host (ByteString -> Host) -> ByteString -> Host
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
encodeUtf8 (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ Text
region Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
".battle.net"

oAuth2BattleNet
  :: YesodAuth m => Text -> Text -> Text -> WidgetFor m () -> AuthPlugin m
oAuth2BattleNet :: Text -> Text -> Text -> WidgetFor m () -> AuthPlugin m
oAuth2BattleNet Text
i Text
s Text
r WidgetFor m ()
w = WidgetFor m () -> Text -> Text -> Text -> AuthPlugin m
forall m.
YesodAuth m =>
WidgetFor m () -> Text -> Text -> Text -> AuthPlugin m
oauth2BattleNet WidgetFor m ()
w Text
r Text
i Text
s
{-# DEPRECATED oAuth2BattleNet "Use oauth2BattleNet" #-}