{-# LANGUAGE OverloadedStrings #-}
-- |
-- OAuth2 plugin for https://slack.com/
--
-- * Authenticates against slack
-- * Uses slack user id as credentials identifier
--
module Yesod.Auth.OAuth2.Slack
  ( SlackScope(..)
  , oauth2Slack
  , oauth2SlackScoped
  ) where

import Yesod.Auth.OAuth2.Prelude

import Network.HTTP.Client
    (httpLbs, parseUrlThrow, responseBody, setQueryString)
import Yesod.Auth.OAuth2.Exception as YesodOAuth2Exception

data SlackScope
    = SlackBasicScope
    | SlackEmailScope
    | SlackTeamScope
    | SlackAvatarScope

scopeText :: SlackScope -> Text
scopeText :: SlackScope -> Text
scopeText SlackScope
SlackBasicScope  = Text
"identity.basic"
scopeText SlackScope
SlackEmailScope  = Text
"identity.email"
scopeText SlackScope
SlackTeamScope   = Text
"identity.team"
scopeText SlackScope
SlackAvatarScope = Text
"identity.avatar"

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
root -> do
    Object
o <- Object
root Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"user"
    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
"slack"

defaultScopes :: [SlackScope]
defaultScopes :: [SlackScope]
defaultScopes = [SlackScope
SlackBasicScope]

oauth2Slack :: YesodAuth m => Text -> Text -> AuthPlugin m
oauth2Slack :: Text -> Text -> AuthPlugin m
oauth2Slack = [SlackScope] -> Text -> Text -> AuthPlugin m
forall m.
YesodAuth m =>
[SlackScope] -> Text -> Text -> AuthPlugin m
oauth2SlackScoped [SlackScope]
defaultScopes

oauth2SlackScoped
  :: YesodAuth m => [SlackScope] -> Text -> Text -> AuthPlugin m
oauth2SlackScoped :: [SlackScope] -> Text -> Text -> AuthPlugin m
oauth2SlackScoped [SlackScope]
scopes Text
clientId Text
clientSecret =
  Text -> OAuth2 -> FetchCreds m -> AuthPlugin m
forall m.
YesodAuth m =>
Text -> OAuth2 -> FetchCreds m -> AuthPlugin m
authOAuth2 Text
pluginName OAuth2
oauth2 (FetchCreds m -> AuthPlugin m) -> FetchCreds m -> AuthPlugin m
forall a b. (a -> b) -> a -> b
$ \Manager
manager OAuth2Token
token -> do
    let param :: ByteString
param = 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
    Request
req <- [(ByteString, Maybe ByteString)] -> Request -> Request
setQueryString [(ByteString
"token", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
param)]
      (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
parseUrlThrow String
"https://slack.com/api/users.identity"
    ByteString
userResponse <- Response ByteString -> ByteString
forall body. Response body -> body
responseBody (Response ByteString -> ByteString)
-> IO (Response ByteString) -> IO ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Request -> Manager -> IO (Response ByteString)
httpLbs Request
req Manager
manager

    (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. (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 (f :: * -> *) a. Applicative f => a -> f a
pure Creds :: forall master. Text -> Text -> [(Text, Text)] -> Creds master
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
  oauth2 :: OAuth2
oauth2 = OAuth2 :: Text
-> Maybe Text
-> URIRef Absolute
-> URIRef Absolute
-> Maybe (URIRef Absolute)
-> OAuth2
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://slack.com/oauth/authorize"
                                  URIRef Absolute -> [(ByteString, ByteString)] -> URIRef Absolute
forall a. URIRef a -> [(ByteString, ByteString)] -> URIRef a
`withQuery` [ Text -> [Text] -> (ByteString, ByteString)
scopeParam Text
","
                                                  ([Text] -> (ByteString, ByteString))
-> [Text] -> (ByteString, ByteString)
forall a b. (a -> b) -> a -> b
$ (SlackScope -> Text) -> [SlackScope] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map SlackScope -> Text
scopeText [SlackScope]
scopes
                                              ]
    , oauth2TokenEndpoint :: URIRef Absolute
oauth2TokenEndpoint     = URIRef Absolute
"https://slack.com/api/oauth.access"
    , oauth2RedirectUri :: Maybe (URIRef Absolute)
oauth2RedirectUri       = Maybe (URIRef Absolute)
forall a. Maybe a
Nothing
    }