yesod-auth-oauth2/Yesod/Auth/OAuth2/Nylas.hs
patrick brisbin 937ad572a3 Update to LTS-9.5 and hoauth2 1.3.0
The largest changes were around the hoauth2 interface:

The OAuth2 type replaced all of its ByteString fields with either Text
or URI. This is a huge improvement. The fields that are now Text are the
type we had them in anyway. The fields that are now URI are type safe
and easier to manipulate. For example, we were doing very unsafe query
string manipulations looking for raw ? or & values, but now we can work
with tuples in a well-typed property.

Additionally the AccessToken type was upgraded to OAuth2Token with an
accessToken field, and the simple Either ByteString a results were
replaced by a real OAuth2Error type. This required changes to our
InvalidProfileResponse mechanism to support.

To make working with uri-bytestring more convenient, an Extension
library was added with some useful instances and helper functions. This
library may be upstreamed at some point.
2017-10-18 17:21:47 -04:00

87 lines
2.8 KiB
Haskell

{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
module Yesod.Auth.OAuth2.Nylas
( oauth2Nylas
, module Yesod.Auth.OAuth2
) where
#if __GLASGOW_HASKELL__ < 710
import Control.Applicative ((<$>), (<*>))
#endif
import Control.Monad (mzero)
import Control.Exception.Lifted (throwIO)
import Data.Aeson (FromJSON, Value(..), parseJSON, decode, (.:))
import Data.Text (Text)
import Data.Text.Encoding (encodeUtf8)
import Network.HTTP.Client (applyBasicAuth, httpLbs, parseRequest, responseBody,
responseStatus)
import Network.HTTP.Conduit (Manager)
import Yesod.Auth (Creds(..), YesodAuth, AuthPlugin)
import Yesod.Auth.OAuth2
import qualified Network.HTTP.Types as HT
data NylasAccount = NylasAccount
{ nylasAccountId :: Text
, nylasAccountEmailAddress :: Text
, nylasAccountName :: Text
, nylasAccountProvider :: Text
, nylasAccountOrganizationUnit :: Text
}
instance FromJSON NylasAccount where
parseJSON (Object o) = NylasAccount
<$> o .: "id"
<*> o .: "email_address"
<*> o .: "name"
<*> o .: "provider"
<*> o .: "organization_unit"
parseJSON _ = mzero
oauth2Nylas :: YesodAuth m
=> Text -- ^ Client ID
-> Text -- ^ Client Secret
-> AuthPlugin m
oauth2Nylas clientId clientSecret = authOAuth2 "nylas" oauth fetchCreds
where
oauth = OAuth2
{ oauthClientId = clientId
, oauthClientSecret = clientSecret
, oauthOAuthorizeEndpoint = "https://api.nylas.com/oauth/authorize" `withQuery`
[ ("response_type", "code")
, ("scope", "email")
, ("client_id", encodeUtf8 clientId)
]
, oauthAccessTokenEndpoint = "https://api.nylas.com/oauth/token"
, oauthCallback = Nothing
}
fetchCreds :: Manager -> OAuth2Token -> IO (Creds a)
fetchCreds manager token = do
req <- authorize <$> parseRequest "https://api.nylas.com/account"
resp <- httpLbs req manager
if HT.statusIsSuccessful (responseStatus resp)
then case decode (responseBody resp) of
Just ns -> return $ toCreds ns token
Nothing -> throwIO parseFailure
else throwIO requestFailure
where
authorize = applyBasicAuth (encodeUtf8 $ atoken $ accessToken token) ""
parseFailure = InvalidProfileResponse "nylas" "failed to parse account"
requestFailure = InvalidProfileResponse "nylas" "failed to get account"
toCreds :: NylasAccount -> OAuth2Token -> Creds a
toCreds ns token = Creds
{ credsPlugin = "nylas"
, credsIdent = nylasAccountId ns
, credsExtra =
[ ("email_address", nylasAccountEmailAddress ns)
, ("name", nylasAccountName ns)
, ("provider", nylasAccountProvider ns)
, ("organization_unit", nylasAccountOrganizationUnit ns)
, ("access_token", atoken $ accessToken token)
]
}