{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}

-- | Bindings Access Token and Refresh Token part of The OAuth 2.0 Authorization Framework
-- RFC6749 <https://www.rfc-editor.org/rfc/rfc6749>
module Network.OAuth.OAuth2.TokenRequest where

import Control.Monad.IO.Class (MonadIO (..))
import Control.Monad.Trans.Except (ExceptT (..), throwE)
import Data.Aeson
import qualified Data.Aeson.Key as Key
import qualified Data.Aeson.KeyMap as KeyMap
import qualified Data.ByteString.Lazy.Char8 as BSL
import qualified Data.Text.Encoding as T
import GHC.Generics (Generic)
import Network.HTTP.Conduit
import qualified Network.HTTP.Types as HT
import Network.HTTP.Types.URI (parseQuery)
import Network.OAuth.OAuth2.Internal
import URI.ByteString (URI, serializeURIRef')

--------------------------------------------------

-- * Token Request Errors

--------------------------------------------------

instance FromJSON Errors where
  parseJSON :: Value -> Parser Errors
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions {constructorTagModifier :: String -> String
constructorTagModifier = Char -> String -> String
camelTo2 Char
'_', allNullaryToStringTag :: Bool
allNullaryToStringTag = Bool
True}

instance ToJSON Errors where
  toEncoding :: Errors -> Encoding
toEncoding = forall a.
(Generic a, GToJSON' Encoding Zero (Rep a)) =>
Options -> a -> Encoding
genericToEncoding Options
defaultOptions {constructorTagModifier :: String -> String
constructorTagModifier = Char -> String -> String
camelTo2 Char
'_', allNullaryToStringTag :: Bool
allNullaryToStringTag = Bool
True}

-- | Token Error Responses https://tools.ietf.org/html/rfc6749#section-5.2
data Errors
  = InvalidRequest
  | InvalidClient
  | InvalidGrant
  | UnauthorizedClient
  | UnsupportedGrantType
  | InvalidScope
  deriving (Int -> Errors -> String -> String
[Errors] -> String -> String
Errors -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Errors] -> String -> String
$cshowList :: [Errors] -> String -> String
show :: Errors -> String
$cshow :: Errors -> String
showsPrec :: Int -> Errors -> String -> String
$cshowsPrec :: Int -> Errors -> String -> String
Show, Errors -> Errors -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Errors -> Errors -> Bool
$c/= :: Errors -> Errors -> Bool
== :: Errors -> Errors -> Bool
$c== :: Errors -> Errors -> Bool
Eq, forall x. Rep Errors x -> Errors
forall x. Errors -> Rep Errors x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Errors x -> Errors
$cfrom :: forall x. Errors -> Rep Errors x
Generic)

--------------------------------------------------

-- * URL

--------------------------------------------------

-- | Prepare the URL and the request body query for fetching an access token.
accessTokenUrl ::
  OAuth2 ->
  -- | access code gained via authorization URL
  ExchangeToken ->
  -- | access token request URL plus the request body.
  (URI, PostBody)
accessTokenUrl :: OAuth2 -> ExchangeToken -> (URI, PostBody)
accessTokenUrl OAuth2
oa ExchangeToken
code =
  let uri :: URI
uri = OAuth2 -> URI
oauth2TokenEndpoint OAuth2
oa
      body :: PostBody
body =
        [ (ByteString
"code", Text -> ByteString
T.encodeUtf8 forall a b. (a -> b) -> a -> b
$ ExchangeToken -> Text
extoken ExchangeToken
code),
          (ByteString
"redirect_uri", forall a. URIRef a -> ByteString
serializeURIRef' forall a b. (a -> b) -> a -> b
$ OAuth2 -> URI
oauth2RedirectUri OAuth2
oa),
          (ByteString
"grant_type", ByteString
"authorization_code")
        ]
   in (URI
uri, PostBody
body)

-- | Obtain a new access token by sending a Refresh Token to the Authorization server.
refreshAccessTokenUrl ::
  OAuth2 ->
  -- | Refresh Token gained via authorization URL
  RefreshToken ->
  -- | Refresh Token request URL plus the request body.
  (URI, PostBody)
refreshAccessTokenUrl :: OAuth2 -> RefreshToken -> (URI, PostBody)
refreshAccessTokenUrl OAuth2
oa RefreshToken
token = (URI
uri, PostBody
body)
  where
    uri :: URI
uri = OAuth2 -> URI
oauth2TokenEndpoint OAuth2
oa
    body :: PostBody
body =
      [ (ByteString
"grant_type", ByteString
"refresh_token"),
        (ByteString
"refresh_token", Text -> ByteString
T.encodeUtf8 forall a b. (a -> b) -> a -> b
$ RefreshToken -> Text
rtoken RefreshToken
token)
      ]

--------------------------------------------------

-- * Token management

--------------------------------------------------

-- | Exchange @code@ for an Access Token with authenticate in request header.
fetchAccessToken ::
  (MonadIO m) =>
  -- | HTTP connection manager
  Manager ->
  -- | OAuth Data
  OAuth2 ->
  -- | OAuth2 Code
  ExchangeToken ->
  -- | Access Token
  ExceptT (OAuth2Error Errors) m OAuth2Token
fetchAccessToken :: forall (m :: * -> *).
MonadIO m =>
Manager
-> OAuth2
-> ExchangeToken
-> ExceptT (OAuth2Error Errors) m OAuth2Token
fetchAccessToken = forall (m :: * -> *).
MonadIO m =>
ClientAuthenticationMethod
-> Manager
-> OAuth2
-> ExchangeToken
-> ExceptT (OAuth2Error Errors) m OAuth2Token
fetchAccessTokenWithAuthMethod ClientAuthenticationMethod
ClientSecretBasic

fetchAccessToken2 ::
  (MonadIO m) =>
  -- | HTTP connection manager
  Manager ->
  -- | OAuth Data
  OAuth2 ->
  -- | Authorization Code
  ExchangeToken ->
  -- | Access Token
  ExceptT (OAuth2Error Errors) m OAuth2Token
fetchAccessToken2 :: forall (m :: * -> *).
MonadIO m =>
Manager
-> OAuth2
-> ExchangeToken
-> ExceptT (OAuth2Error Errors) m OAuth2Token
fetchAccessToken2 = forall (m :: * -> *).
MonadIO m =>
ClientAuthenticationMethod
-> Manager
-> OAuth2
-> ExchangeToken
-> ExceptT (OAuth2Error Errors) m OAuth2Token
fetchAccessTokenWithAuthMethod ClientAuthenticationMethod
ClientSecretPost
{-# DEPRECATED fetchAccessToken2 "use 'fetchAccessTokenWithAuthMethod'" #-}

fetchAccessTokenInternal ::
  (MonadIO m) =>
  ClientAuthenticationMethod ->
  -- | HTTP connection manager
  Manager ->
  -- | OAuth Data
  OAuth2 ->
  -- | Authorization Code
  ExchangeToken ->
  -- | Access Token
  ExceptT (OAuth2Error Errors) m OAuth2Token
fetchAccessTokenInternal :: forall (m :: * -> *).
MonadIO m =>
ClientAuthenticationMethod
-> Manager
-> OAuth2
-> ExchangeToken
-> ExceptT (OAuth2Error Errors) m OAuth2Token
fetchAccessTokenInternal = forall (m :: * -> *).
MonadIO m =>
ClientAuthenticationMethod
-> Manager
-> OAuth2
-> ExchangeToken
-> ExceptT (OAuth2Error Errors) m OAuth2Token
fetchAccessTokenWithAuthMethod
{-# DEPRECATED fetchAccessTokenInternal "use 'fetchAccessTokenWithAuthMethod'" #-}

-- | Exchange @code@ for an Access Token
--
-- OAuth2 spec allows credential (`client_id`, `client_secret`) to be sent
-- either in the header (a.k.a 'ClientSecretBasic').
-- or as form/url params (a.k.a 'ClientSecretPost').
--
-- The OAuth provider can choose to implement only one, or both.
-- Look for API document from the OAuth provider you're dealing with.
-- If you're uncertain, try 'fetchAccessToken' which sends credential
-- in authorization http header, which is common case.
--
-- @since 2.6.0
fetchAccessTokenWithAuthMethod ::
  (MonadIO m) =>
  ClientAuthenticationMethod ->
  -- | HTTP connection manager
  Manager ->
  -- | OAuth Data
  OAuth2 ->
  -- | Authorization Code
  ExchangeToken ->
  -- | Access Token
  ExceptT (OAuth2Error Errors) m OAuth2Token
fetchAccessTokenWithAuthMethod :: forall (m :: * -> *).
MonadIO m =>
ClientAuthenticationMethod
-> Manager
-> OAuth2
-> ExchangeToken
-> ExceptT (OAuth2Error Errors) m OAuth2Token
fetchAccessTokenWithAuthMethod ClientAuthenticationMethod
authMethod Manager
manager OAuth2
oa ExchangeToken
code = do
  let (URI
uri, PostBody
body) = OAuth2 -> ExchangeToken -> (URI, PostBody)
accessTokenUrl OAuth2
oa ExchangeToken
code
  let extraBody :: PostBody
extraBody = if ClientAuthenticationMethod
authMethod forall a. Eq a => a -> a -> Bool
== ClientAuthenticationMethod
ClientSecretPost then OAuth2 -> PostBody
clientSecretPost OAuth2
oa else []
  forall (m :: * -> *) err a.
(MonadIO m, FromJSON err, FromJSON a) =>
Manager
-> OAuth2 -> URI -> PostBody -> ExceptT (OAuth2Error err) m a
doJSONPostRequest Manager
manager OAuth2
oa URI
uri (PostBody
body forall a. [a] -> [a] -> [a]
++ PostBody
extraBody)

-- | Fetch a new AccessToken using the Refresh Token with authentication in request header.
refreshAccessToken ::
  (MonadIO m) =>
  -- | HTTP connection manager.
  Manager ->
  -- | OAuth context
  OAuth2 ->
  -- | Refresh Token gained after authorization
  RefreshToken ->
  ExceptT (OAuth2Error Errors) m OAuth2Token
refreshAccessToken :: forall (m :: * -> *).
MonadIO m =>
Manager
-> OAuth2
-> RefreshToken
-> ExceptT (OAuth2Error Errors) m OAuth2Token
refreshAccessToken = forall (m :: * -> *).
MonadIO m =>
ClientAuthenticationMethod
-> Manager
-> OAuth2
-> RefreshToken
-> ExceptT (OAuth2Error Errors) m OAuth2Token
refreshAccessTokenWithAuthMethod ClientAuthenticationMethod
ClientSecretBasic

refreshAccessToken2 ::
  (MonadIO m) =>
  -- | HTTP connection manager.
  Manager ->
  -- | OAuth context
  OAuth2 ->
  -- | Refresh Token gained after authorization
  RefreshToken ->
  ExceptT (OAuth2Error Errors) m OAuth2Token
refreshAccessToken2 :: forall (m :: * -> *).
MonadIO m =>
Manager
-> OAuth2
-> RefreshToken
-> ExceptT (OAuth2Error Errors) m OAuth2Token
refreshAccessToken2 = forall (m :: * -> *).
MonadIO m =>
ClientAuthenticationMethod
-> Manager
-> OAuth2
-> RefreshToken
-> ExceptT (OAuth2Error Errors) m OAuth2Token
refreshAccessTokenWithAuthMethod ClientAuthenticationMethod
ClientSecretPost
{-# DEPRECATED refreshAccessToken2 "use 'refreshAccessTokenWithAuthMethod'" #-}

refreshAccessTokenInternal ::
  (MonadIO m) =>
  ClientAuthenticationMethod ->
  -- | HTTP connection manager.
  Manager ->
  -- | OAuth context
  OAuth2 ->
  -- | Refresh Token gained after authorization
  RefreshToken ->
  ExceptT (OAuth2Error Errors) m OAuth2Token
refreshAccessTokenInternal :: forall (m :: * -> *).
MonadIO m =>
ClientAuthenticationMethod
-> Manager
-> OAuth2
-> RefreshToken
-> ExceptT (OAuth2Error Errors) m OAuth2Token
refreshAccessTokenInternal = forall (m :: * -> *).
MonadIO m =>
ClientAuthenticationMethod
-> Manager
-> OAuth2
-> RefreshToken
-> ExceptT (OAuth2Error Errors) m OAuth2Token
refreshAccessTokenWithAuthMethod
{-# DEPRECATED refreshAccessTokenInternal "use 'refreshAccessTokenWithAuthMethod'" #-}

-- | Fetch a new AccessToken using the Refresh Token.
--
-- OAuth2 spec allows credential (`client_id`, `client_secret`) to be sent
-- either in the header (a.k.a 'ClientSecretBasic').
-- or as form/url params (a.k.a 'ClientSecretPost').
--
-- The OAuth provider can choose to implement only one, or both.
-- Look for API document from the OAuth provider you're dealing with.
-- If you're uncertain, try 'refreshAccessToken' which sends credential
-- in authorization http header, which is common case.
--
-- @since 2.6.0
refreshAccessTokenWithAuthMethod ::
  (MonadIO m) =>
  ClientAuthenticationMethod ->
  -- | HTTP connection manager.
  Manager ->
  -- | OAuth context
  OAuth2 ->
  -- | Refresh Token gained after authorization
  RefreshToken ->
  ExceptT (OAuth2Error Errors) m OAuth2Token
refreshAccessTokenWithAuthMethod :: forall (m :: * -> *).
MonadIO m =>
ClientAuthenticationMethod
-> Manager
-> OAuth2
-> RefreshToken
-> ExceptT (OAuth2Error Errors) m OAuth2Token
refreshAccessTokenWithAuthMethod ClientAuthenticationMethod
authMethod Manager
manager OAuth2
oa RefreshToken
token = do
  let (URI
uri, PostBody
body) = OAuth2 -> RefreshToken -> (URI, PostBody)
refreshAccessTokenUrl OAuth2
oa RefreshToken
token
  let extraBody :: PostBody
extraBody = if ClientAuthenticationMethod
authMethod forall a. Eq a => a -> a -> Bool
== ClientAuthenticationMethod
ClientSecretPost then OAuth2 -> PostBody
clientSecretPost OAuth2
oa else []
  forall (m :: * -> *) err a.
(MonadIO m, FromJSON err, FromJSON a) =>
Manager
-> OAuth2 -> URI -> PostBody -> ExceptT (OAuth2Error err) m a
doJSONPostRequest Manager
manager OAuth2
oa URI
uri (PostBody
body forall a. [a] -> [a] -> [a]
++ PostBody
extraBody)

--------------------------------------------------

-- * Utilies

--------------------------------------------------

-- | Conduct post request and return response as JSON.
doJSONPostRequest ::
  (MonadIO m, FromJSON err, FromJSON a) =>
  -- | HTTP connection manager.
  Manager ->
  -- | OAuth options
  OAuth2 ->
  -- | The URL
  URI ->
  -- | request body
  PostBody ->
  -- | Response as JSON
  ExceptT (OAuth2Error err) m a
doJSONPostRequest :: forall (m :: * -> *) err a.
(MonadIO m, FromJSON err, FromJSON a) =>
Manager
-> OAuth2 -> URI -> PostBody -> ExceptT (OAuth2Error err) m a
doJSONPostRequest Manager
manager OAuth2
oa URI
uri PostBody
body = do
  ByteString
resp <- forall (m :: * -> *) err.
(MonadIO m, FromJSON err) =>
Manager
-> OAuth2
-> URI
-> PostBody
-> ExceptT (OAuth2Error err) m ByteString
doSimplePostRequest Manager
manager OAuth2
oa URI
uri PostBody
body
  case forall err a.
(FromJSON err, FromJSON a) =>
ByteString -> Either (OAuth2Error err) a
parseResponseFlexible ByteString
resp of
    Right a
obj -> forall (m :: * -> *) a. Monad m => a -> m a
return a
obj
    Left OAuth2Error err
e -> forall (m :: * -> *) e a. Monad m => e -> ExceptT e m a
throwE OAuth2Error err
e

-- | Conduct post request.
doSimplePostRequest ::
  (MonadIO m, FromJSON err) =>
  -- | HTTP connection manager.
  Manager ->
  -- | OAuth options
  OAuth2 ->
  -- | URL
  URI ->
  -- | Request body.
  PostBody ->
  -- | Response as ByteString
  ExceptT (OAuth2Error err) m BSL.ByteString
doSimplePostRequest :: forall (m :: * -> *) err.
(MonadIO m, FromJSON err) =>
Manager
-> OAuth2
-> URI
-> PostBody
-> ExceptT (OAuth2Error err) m ByteString
doSimplePostRequest Manager
manager OAuth2
oa URI
url PostBody
body =
  forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall err.
FromJSON err =>
Response ByteString -> Either (OAuth2Error err) ByteString
handleOAuth2TokenResponse IO (Response ByteString)
go
  where
    addBasicAuth :: Request -> Request
addBasicAuth = ByteString -> ByteString -> Request -> Request
applyBasicAuth (Text -> ByteString
T.encodeUtf8 forall a b. (a -> b) -> a -> b
$ OAuth2 -> Text
oauth2ClientId OAuth2
oa) (Text -> ByteString
T.encodeUtf8 forall a b. (a -> b) -> a -> b
$ OAuth2 -> Text
oauth2ClientSecret OAuth2
oa)
    go :: IO (Response ByteString)
go = do
      Request
req <- forall (m :: * -> *). MonadThrow m => URI -> m Request
uriToRequest URI
url
      let req' :: Request
req' = (Request -> Request
addBasicAuth forall b c a. (b -> c) -> (a -> b) -> a -> c
. Request -> Request
addDefaultRequestHeaders) Request
req
      forall (m :: * -> *).
MonadIO m =>
Request -> Manager -> m (Response ByteString)
httpLbs (PostBody -> Request -> Request
urlEncodedBody PostBody
body Request
req') Manager
manager

-- | Gets response body from a @Response@ if 200 otherwise assume 'OAuth2Error'
handleOAuth2TokenResponse :: FromJSON err => Response BSL.ByteString -> Either (OAuth2Error err) BSL.ByteString
handleOAuth2TokenResponse :: forall err.
FromJSON err =>
Response ByteString -> Either (OAuth2Error err) ByteString
handleOAuth2TokenResponse Response ByteString
rsp =
  if Status -> Bool
HT.statusIsSuccessful (forall body. Response body -> Status
responseStatus Response ByteString
rsp)
    then forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall body. Response body -> body
responseBody Response ByteString
rsp
    else forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ forall err. FromJSON err => ByteString -> OAuth2Error err
parseOAuth2Error (forall body. Response body -> body
responseBody Response ByteString
rsp)

-- | Try to parses response as JSON, if failed, try to parse as like query string.
parseResponseFlexible ::
  (FromJSON err, FromJSON a) =>
  BSL.ByteString ->
  Either (OAuth2Error err) a
parseResponseFlexible :: forall err a.
(FromJSON err, FromJSON a) =>
ByteString -> Either (OAuth2Error err) a
parseResponseFlexible ByteString
r = case forall a. FromJSON a => ByteString -> Either String a
eitherDecode ByteString
r of
  Left String
_ -> forall err a.
(FromJSON err, FromJSON a) =>
ByteString -> Either (OAuth2Error err) a
parseResponseString ByteString
r
  Right a
x -> forall a b. b -> Either a b
Right a
x

-- | Parses the response that contains not JSON but a Query String
parseResponseString ::
  (FromJSON err, FromJSON a) =>
  BSL.ByteString ->
  Either (OAuth2Error err) a
parseResponseString :: forall err a.
(FromJSON err, FromJSON a) =>
ByteString -> Either (OAuth2Error err) a
parseResponseString ByteString
b = case ByteString -> Query
parseQuery forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
BSL.toStrict ByteString
b of
  [] -> forall a b. a -> Either a b
Left OAuth2Error err
errorMessage
  Query
a -> case forall a. FromJSON a => Value -> Result a
fromJSON forall a b. (a -> b) -> a -> b
$ Query -> Value
queryToValue Query
a of
    Error String
_ -> forall a b. a -> Either a b
Left OAuth2Error err
errorMessage
    Success a
x -> forall a b. b -> Either a b
Right a
x
  where
    queryToValue :: Query -> Value
queryToValue = Object -> Value
Object forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall v. [(Key, v)] -> KeyMap v
KeyMap.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (ByteString, Maybe ByteString) -> Pair
paramToPair
    paramToPair :: (ByteString, Maybe ByteString) -> Pair
paramToPair (ByteString
k, Maybe ByteString
mv) = (Text -> Key
Key.fromText forall a b. (a -> b) -> a -> b
$ ByteString -> Text
T.decodeUtf8 ByteString
k, forall b a. b -> (a -> b) -> Maybe a -> b
maybe Value
Null (Text -> Value
String forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
T.decodeUtf8) Maybe ByteString
mv)
    errorMessage :: OAuth2Error err
errorMessage = forall err. FromJSON err => ByteString -> OAuth2Error err
parseOAuth2Error ByteString
b

-- | Set several header values:
--   + userAgennt    : `hoauth2`
--   + accept        : `application/json`
addDefaultRequestHeaders :: Request -> Request
addDefaultRequestHeaders :: Request -> Request
addDefaultRequestHeaders Request
req =
  let headers :: [(HeaderName, ByteString)]
headers = [(HeaderName, ByteString)]
defaultRequestHeaders forall a. [a] -> [a] -> [a]
++ Request -> [(HeaderName, ByteString)]
requestHeaders Request
req
   in Request
req {requestHeaders :: [(HeaderName, ByteString)]
requestHeaders = [(HeaderName, ByteString)]
headers}

-- | Add Credential (client_id, client_secret) to the request post body.
clientSecretPost :: OAuth2 -> PostBody
clientSecretPost :: OAuth2 -> PostBody
clientSecretPost OAuth2
oa =
  [ (ByteString
"client_id", Text -> ByteString
T.encodeUtf8 forall a b. (a -> b) -> a -> b
$ OAuth2 -> Text
oauth2ClientId OAuth2
oa),
    (ByteString
"client_secret", Text -> ByteString
T.encodeUtf8 forall a b. (a -> b) -> a -> b
$ OAuth2 -> Text
oauth2ClientSecret OAuth2
oa)
  ]