{-# LANGUAGE OverloadedStrings #-}

module Yesod.Auth.OAuth2.Nylas
  ( oauth2Nylas
  ) where

import Yesod.Auth.OAuth2.Prelude

import Control.Monad (unless)
import qualified Data.ByteString.Lazy.Char8 as BL8
import Network.HTTP.Client
import qualified Network.HTTP.Types as HT
import qualified Yesod.Auth.OAuth2.Exception as YesodOAuth2Exception

newtype User = User Text

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

pluginName :: Text
pluginName :: Text
pluginName = Text
"nylas"

defaultScopes :: [Text]
defaultScopes :: [Text]
defaultScopes = [Text
"email"]

oauth2Nylas :: YesodAuth m => Text -> Text -> AuthPlugin m
oauth2Nylas :: forall m. YesodAuth m => Text -> Text -> AuthPlugin m
oauth2Nylas Text
clientId Text
clientSecret =
  Text -> OAuth2 -> FetchCreds m -> AuthPlugin m
forall m.
YesodAuth m =>
Text -> OAuth2 -> FetchCreds m -> AuthPlugin m
authOAuth2 Text
pluginName OAuth2
oauth (FetchCreds m -> AuthPlugin m) -> FetchCreds m -> AuthPlugin m
forall a b. (a -> b) -> a -> b
$ \Manager
manager OAuth2Token
token -> do
    Request
req <-
      ByteString -> ByteString -> Request -> Request
applyBasicAuth (Text -> ByteString
encodeUtf8 (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ AccessToken -> Text
atoken (AccessToken -> Text) -> AccessToken -> Text
forall a b. (a -> b) -> a -> b
$ OAuth2Token -> AccessToken
accessToken OAuth2Token
token) ByteString
""
        (Request -> Request) -> IO Request -> IO Request
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO Request
forall (m :: * -> *). MonadThrow m => String -> m Request
parseRequest String
"https://api.nylas.com/account"
    Response ByteString
resp <- Request -> Manager -> IO (Response ByteString)
httpLbs Request
req Manager
manager
    let userResponse :: ByteString
userResponse = Response ByteString -> ByteString
forall body. Response body -> body
responseBody Response ByteString
resp

    -- FIXME: was this working? I'm 95% sure that the client will throw its
    -- own exception on unsuccessful status codes.
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Status -> Bool
HT.statusIsSuccessful (Status -> Bool) -> Status -> Bool
forall a b. (a -> b) -> a -> b
$ Response ByteString -> Status
forall body. Response body -> Status
responseStatus Response ByteString
resp) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
      YesodOAuth2Exception -> IO ()
forall (m :: * -> *) e a.
(HasCallStack, MonadThrow m, Exception e) =>
e -> m a
throwIO (YesodOAuth2Exception -> IO ()) -> YesodOAuth2Exception -> IO ()
forall a b. (a -> b) -> a -> b
$
        Text -> String -> YesodOAuth2Exception
YesodOAuth2Exception.GenericError Text
pluginName (String -> YesodOAuth2Exception) -> String -> YesodOAuth2Exception
forall a b. (a -> b) -> a -> b
$
          String
"Unsuccessful HTTP response: "
            String -> String -> String
forall a. Semigroup a => a -> a -> a
<> ByteString -> String
BL8.unpack ByteString
userResponse

    (String -> IO (Creds m))
-> (User -> IO (Creds m)) -> Either String User -> IO (Creds m)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
      (YesodOAuth2Exception -> IO (Creds m)
forall (m :: * -> *) e a.
(HasCallStack, MonadThrow m, Exception e) =>
e -> m a
throwIO (YesodOAuth2Exception -> IO (Creds m))
-> (String -> YesodOAuth2Exception) -> String -> IO (Creds m)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String -> YesodOAuth2Exception
YesodOAuth2Exception.JSONDecodingError Text
pluginName)
      ( \(User Text
userId) ->
          Creds m -> IO (Creds m)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
            Creds
              { credsPlugin :: Text
credsPlugin = Text
pluginName
              , credsIdent :: Text
credsIdent = Text
userId
              , credsExtra :: [(Text, Text)]
credsExtra = OAuth2Token -> ByteString -> [(Text, Text)]
setExtra OAuth2Token
token ByteString
userResponse
              }
      )
      (Either String User -> IO (Creds m))
-> Either String User -> IO (Creds m)
forall a b. (a -> b) -> a -> b
$ ByteString -> Either String User
forall a. FromJSON a => ByteString -> Either String a
eitherDecode ByteString
userResponse
 where
  oauth :: OAuth2
oauth =
    OAuth2
      { oauth2ClientId :: Text
oauth2ClientId = Text
clientId
      , oauth2ClientSecret :: Maybe Text
oauth2ClientSecret = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
clientSecret
      , oauth2AuthorizeEndpoint :: URIRef Absolute
oauth2AuthorizeEndpoint =
          URIRef Absolute
"https://api.nylas.com/oauth/authorize"
            URIRef Absolute -> [(ByteString, ByteString)] -> URIRef Absolute
forall a. URIRef a -> [(ByteString, ByteString)] -> URIRef a
`withQuery` [ (ByteString
"response_type", ByteString
"code")
                        , (ByteString
"client_id", Text -> ByteString
encodeUtf8 Text
clientId)
                        , -- N.B. The scopes delimeter is unknown/untested. Verify that before
                          -- extracting this to an argument and offering a Scoped function. In
                          -- its current state, it doesn't matter because it's only one scope.
                          Text -> [Text] -> (ByteString, ByteString)
scopeParam Text
"," [Text]
defaultScopes
                        ]
      , oauth2TokenEndpoint :: URIRef Absolute
oauth2TokenEndpoint = URIRef Absolute
"https://api.nylas.com/oauth/token"
      , oauth2RedirectUri :: Maybe (URIRef Absolute)
oauth2RedirectUri = Maybe (URIRef Absolute)
forall a. Maybe a
Nothing
      }