{-# LANGUAGE OverloadedStrings #-}

module Yesod.Auth.OAuth2.WordPressDotCom
  ( oauth2WordPressDotCom
  ) where

import qualified Data.Text as T
import Yesod.Auth.OAuth2.Prelude

pluginName :: Text
pluginName :: Text
pluginName = Text
"WordPress.com"

newtype WpUser = WpUser Int

instance FromJSON WpUser where
  parseJSON :: Value -> Parser WpUser
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"WpUser" forall a b. (a -> b) -> a -> b
$ \Object
o -> Int -> WpUser
WpUser forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"ID"

oauth2WordPressDotCom
  :: (YesodAuth m)
  => Text -- ^ Client Id
  -> Text -- ^ Client Secret
  -> AuthPlugin m
oauth2WordPressDotCom :: forall m. YesodAuth m => Text -> Text -> AuthPlugin m
oauth2WordPressDotCom Text
clientId Text
clientSecret =
  forall m.
YesodAuth m =>
Text -> OAuth2 -> FetchCreds m -> AuthPlugin m
authOAuth2 Text
pluginName OAuth2
oauth2 forall a b. (a -> b) -> a -> b
$ \Manager
manager OAuth2Token
token -> do
    (WpUser Int
userId, ByteString
userResponse) <- forall a.
FromJSON a =>
Text -> Manager -> OAuth2Token -> URI -> IO (a, ByteString)
authGetProfile
      Text
pluginName
      Manager
manager
      OAuth2Token
token
      URI
"https://public-api.wordpress.com/rest/v1/me/"

    forall (f :: * -> *) a. Applicative f => a -> f a
pure Creds
      { credsPlugin :: Text
credsPlugin = Text
pluginName
      , credsIdent :: Text
credsIdent = String -> Text
T.pack forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show Int
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 = forall a. a -> Maybe a
Just Text
clientSecret
    , oauth2AuthorizeEndpoint :: URI
oauth2AuthorizeEndpoint =
      URI
"https://public-api.wordpress.com/oauth2/authorize"
        forall a. URIRef a -> [(ByteString, ByteString)] -> URIRef a
`withQuery` [Text -> [Text] -> (ByteString, ByteString)
scopeParam Text
"," [Text
"auth"]]
    , oauth2TokenEndpoint :: URI
oauth2TokenEndpoint = URI
"https://public-api.wordpress.com/oauth2/token"
    , oauth2RedirectUri :: Maybe URI
oauth2RedirectUri = forall a. Maybe a
Nothing
    }