{-# LANGUAGE CPP #-}

module Network.OAuth.OAuth2.Compat
    ( OAuth2(..)
    , OAuth2Result
    , authorizationUrl
    , fetchAccessToken
    , fetchAccessToken2
    , authGetBS

    -- * Re-exports
    , module Network.OAuth.OAuth2
    ) where

import Data.ByteString.Lazy (ByteString)
import Data.Text (Text)
import Network.HTTP.Conduit (Manager)
import Network.OAuth.OAuth2
    ( AccessToken(..)
    , ExchangeToken(..)
    , OAuth2Error
    , OAuth2Token(..)
    , RefreshToken(..)
    )
import qualified Network.OAuth.OAuth2 as OAuth2
import Network.OAuth.OAuth2.TokenRequest (Errors)
import URI.ByteString

#if MIN_VERSION_hoauth2(2,2,0)
import Control.Monad.Trans.Except (ExceptT, runExceptT)
import Data.Maybe (fromMaybe)
#endif

data OAuth2 = OAuth2
    { OAuth2 -> Text
oauth2ClientId :: Text
    , OAuth2 -> Maybe Text
oauth2ClientSecret :: Maybe Text
    , OAuth2 -> URIRef Absolute
oauth2AuthorizeEndpoint :: URIRef Absolute
    , OAuth2 -> URIRef Absolute
oauth2TokenEndpoint :: URIRef Absolute
    , OAuth2 -> Maybe (URIRef Absolute)
oauth2RedirectUri :: Maybe (URIRef Absolute)
    }

type OAuth2Result err a = Either (OAuth2Error err) a

authorizationUrl :: OAuth2 -> URI
authorizationUrl :: OAuth2 -> URIRef Absolute
authorizationUrl = OAuth2 -> URIRef Absolute
OAuth2.authorizationUrl (OAuth2 -> URIRef Absolute)
-> (OAuth2 -> OAuth2) -> OAuth2 -> URIRef Absolute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OAuth2 -> OAuth2
getOAuth2

fetchAccessToken
    :: Manager
    -> OAuth2
    -> ExchangeToken
    -> IO (OAuth2Result Errors OAuth2Token)
fetchAccessToken :: Manager
-> OAuth2 -> ExchangeToken -> IO (OAuth2Result Errors OAuth2Token)
fetchAccessToken = Manager
-> OAuth2 -> ExchangeToken -> IO (OAuth2Result Errors OAuth2Token)
fetchAccessTokenBasic

fetchAccessToken2
    :: Manager
    -> OAuth2
    -> ExchangeToken
    -> IO (OAuth2Result Errors OAuth2Token)
fetchAccessToken2 :: Manager
-> OAuth2 -> ExchangeToken -> IO (OAuth2Result Errors OAuth2Token)
fetchAccessToken2 = Manager
-> OAuth2 -> ExchangeToken -> IO (OAuth2Result Errors OAuth2Token)
fetchAccessTokenPost

authGetBS :: Manager -> AccessToken -> URI -> IO (Either ByteString ByteString)
authGetBS :: Manager
-> AccessToken
-> URIRef Absolute
-> IO (Either ByteString ByteString)
authGetBS Manager
m AccessToken
a URIRef Absolute
u = ExceptT ByteString IO ByteString
-> IO (Either ByteString ByteString)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runOAuth2 (ExceptT ByteString IO ByteString
 -> IO (Either ByteString ByteString))
-> ExceptT ByteString IO ByteString
-> IO (Either ByteString ByteString)
forall a b. (a -> b) -> a -> b
$ Manager
-> AccessToken
-> URIRef Absolute
-> ExceptT ByteString IO ByteString
OAuth2.authGetBS Manager
m AccessToken
a URIRef Absolute
u

-- Normalize the rename of record fields at hoauth2-2.0. Our type is the newer
-- names and we up-convert if hoauth2-1.x is in use. getClientSecret and
-- getRedirectUri handle the differences in hoauth2-2.2 and 2.3.

#if MIN_VERSION_hoauth2(2,0,0)
getOAuth2 :: OAuth2 -> OAuth2.OAuth2
getOAuth2 :: OAuth2 -> OAuth2
getOAuth2 OAuth2
o = OAuth2 :: Text
-> Text
-> URIRef Absolute
-> URIRef Absolute
-> URIRef Absolute
-> OAuth2
OAuth2.OAuth2
    { oauth2ClientId :: Text
OAuth2.oauth2ClientId = OAuth2 -> Text
oauth2ClientId OAuth2
o
    , oauth2ClientSecret :: Text
OAuth2.oauth2ClientSecret = Maybe Text -> Text
getClientSecret (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ OAuth2 -> Maybe Text
oauth2ClientSecret OAuth2
o
    , oauth2AuthorizeEndpoint :: URIRef Absolute
OAuth2.oauth2AuthorizeEndpoint = OAuth2 -> URIRef Absolute
oauth2AuthorizeEndpoint OAuth2
o
    , oauth2TokenEndpoint :: URIRef Absolute
OAuth2.oauth2TokenEndpoint = OAuth2 -> URIRef Absolute
oauth2TokenEndpoint OAuth2
o
    , oauth2RedirectUri :: URIRef Absolute
OAuth2.oauth2RedirectUri = Maybe (URIRef Absolute) -> URIRef Absolute
getRedirectUri (Maybe (URIRef Absolute) -> URIRef Absolute)
-> Maybe (URIRef Absolute) -> URIRef Absolute
forall a b. (a -> b) -> a -> b
$ OAuth2 -> Maybe (URIRef Absolute)
oauth2RedirectUri OAuth2
o
    }
#else
getOAuth2 :: OAuth2 -> OAuth2.OAuth2
getOAuth2 o = OAuth2.OAuth2
    { OAuth2.oauthClientId = oauth2ClientId o
    , OAuth2.oauthClientSecret = getClientSecret $ oauth2ClientSecret o
    , OAuth2.oauthOAuthorizeEndpoint = oauth2AuthorizeEndpoint o
    , OAuth2.oauthAccessTokenEndpoint = oauth2TokenEndpoint o
    , OAuth2.oauthCallback = getRedirectUri $ oauth2RedirectUri o
    }
#endif

-- hoauth2-2.2 made oauth2ClientSecret non-Maybe, after 2.0 had just made it
-- Maybe so we have to adjust, twice. TODO: change ours type to non-Maybe (major
-- bump) and reverse this to up-convert with Just in pre-2.2.

#if MIN_VERSION_hoauth2(2,2,0)
getClientSecret :: Maybe Text -> Text
getClientSecret :: Maybe Text -> Text
getClientSecret =
    Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe (Text -> Maybe Text -> Text) -> Text -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ [Char] -> Text
forall a. HasCallStack => [Char] -> a
error [Char]
"Cannot use OAuth2.oauth2ClientSecret with Nothing"
#else
getClientSecret :: Maybe Text -> Maybe Text
getClientSecret = id
#endif

-- hoauth2-2.3 then made oauth2RedirectUri non-Maybe too. We logically rely on
-- instantiating with Nothing at definition-time, then setting it to the
-- callback at use-time, which means we can't just change our type and invert
-- this shim; we'll have to do something much more pervasive to avoid this
-- fromMaybe.

#if MIN_VERSION_hoauth2(2,3,0)
getRedirectUri :: Maybe (URIRef Absolute) -> (URIRef Absolute)
getRedirectUri :: Maybe (URIRef Absolute) -> URIRef Absolute
getRedirectUri =
    URIRef Absolute -> Maybe (URIRef Absolute) -> URIRef Absolute
forall a. a -> Maybe a -> a
fromMaybe (URIRef Absolute -> Maybe (URIRef Absolute) -> URIRef Absolute)
-> URIRef Absolute -> Maybe (URIRef Absolute) -> URIRef Absolute
forall a b. (a -> b) -> a -> b
$ [Char] -> URIRef Absolute
forall a. HasCallStack => [Char] -> a
error [Char]
"Cannot use OAuth2.oauth2RedirectUri with Nothing"
#else
getRedirectUri :: Maybe (URIRef Absolute) -> Maybe (URIRef Absolute)
getRedirectUri = id
#endif

-- hoauth-2.2 moved most IO-Either functions to ExceptT. This reverses that.

#if MIN_VERSION_hoauth2(2,2,0)
runOAuth2 :: ExceptT e m a -> m (Either e a)
runOAuth2 :: ExceptT e m a -> m (Either e a)
runOAuth2 = ExceptT e m a -> m (Either e a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT
#else
runOAuth2 :: IO (Either e a) -> IO (Either e a)
runOAuth2 = id
#endif

-- The fetchAccessToken functions grew a nicer interface in hoauth2-2.3. This
-- up-converts the older ones. We should update our code to use these functions
-- directly.

fetchAccessTokenBasic
    :: Manager
    -> OAuth2
    -> ExchangeToken
    -> IO (OAuth2Result Errors OAuth2Token)
fetchAccessTokenBasic :: Manager
-> OAuth2 -> ExchangeToken -> IO (OAuth2Result Errors OAuth2Token)
fetchAccessTokenBasic Manager
m OAuth2
o ExchangeToken
e = ExceptT (OAuth2Error Errors) IO OAuth2Token
-> IO (OAuth2Result Errors OAuth2Token)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runOAuth2 (ExceptT (OAuth2Error Errors) IO OAuth2Token
 -> IO (OAuth2Result Errors OAuth2Token))
-> ExceptT (OAuth2Error Errors) IO OAuth2Token
-> IO (OAuth2Result Errors OAuth2Token)
forall a b. (a -> b) -> a -> b
$ Manager
-> OAuth2
-> ExchangeToken
-> ExceptT (OAuth2Error Errors) IO OAuth2Token
f Manager
m (OAuth2 -> OAuth2
getOAuth2 OAuth2
o) ExchangeToken
e
  where
#if MIN_VERSION_hoauth2(2,3,0)
    f :: Manager
-> OAuth2
-> ExchangeToken
-> ExceptT (OAuth2Error Errors) IO OAuth2Token
f = ClientAuthenticationMethod
-> Manager
-> OAuth2
-> ExchangeToken
-> ExceptT (OAuth2Error Errors) IO OAuth2Token
OAuth2.fetchAccessTokenInternal ClientAuthenticationMethod
OAuth2.ClientSecretBasic
#else
    f = OAuth2.fetchAccessToken
#endif

fetchAccessTokenPost
    :: Manager
    -> OAuth2
    -> ExchangeToken
    -> IO (OAuth2Result Errors OAuth2Token)
fetchAccessTokenPost :: Manager
-> OAuth2 -> ExchangeToken -> IO (OAuth2Result Errors OAuth2Token)
fetchAccessTokenPost Manager
m OAuth2
o ExchangeToken
e = ExceptT (OAuth2Error Errors) IO OAuth2Token
-> IO (OAuth2Result Errors OAuth2Token)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runOAuth2 (ExceptT (OAuth2Error Errors) IO OAuth2Token
 -> IO (OAuth2Result Errors OAuth2Token))
-> ExceptT (OAuth2Error Errors) IO OAuth2Token
-> IO (OAuth2Result Errors OAuth2Token)
forall a b. (a -> b) -> a -> b
$ Manager
-> OAuth2
-> ExchangeToken
-> ExceptT (OAuth2Error Errors) IO OAuth2Token
f Manager
m (OAuth2 -> OAuth2
getOAuth2 OAuth2
o) ExchangeToken
e
  where
#if MIN_VERSION_hoauth2(2,3,0)
    f :: Manager
-> OAuth2
-> ExchangeToken
-> ExceptT (OAuth2Error Errors) IO OAuth2Token
f = ClientAuthenticationMethod
-> Manager
-> OAuth2
-> ExchangeToken
-> ExceptT (OAuth2Error Errors) IO OAuth2Token
OAuth2.fetchAccessTokenInternal ClientAuthenticationMethod
OAuth2.ClientSecretPost
#else
    f = OAuth2.fetchAccessToken2
#endif