{-# LANGUAGE OverloadedStrings #-}

module Yesod.Auth.OAuth2.GitLab
  ( oauth2GitLab
  , oauth2GitLabHostScopes
  , defaultHost
  , defaultScopes
  ) where

import Yesod.Auth.OAuth2.Prelude

import qualified Data.Text as T

newtype User = User Int

instance FromJSON User where
  parseJSON :: Value -> Parser User
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"User" forall a b. (a -> b) -> a -> b
$ \Object
o -> Int -> User
User forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"

pluginName :: Text
pluginName :: Text
pluginName = Text
"gitlab"

defaultHost :: URI
defaultHost :: URI
defaultHost = URI
"https://gitlab.com"

defaultScopes :: [Text]
defaultScopes :: [Text]
defaultScopes = [Text
"read_user"]

-- | Authorize with @gitlab.com@ and @[\"read_user\"]@
--
-- To customize either of these values, use @'oauth2GitLabHostScopes'@ and pass
-- the default for the argument not being customized. Note that we require at
-- least @read_user@, so we can request the credentials identifier.
--
-- > oauth2GitLabHostScopes defaultHost ["api", "read_user"]
-- > oauth2GitLabHostScopes "https://gitlab.example.com" defaultScopes
oauth2GitLab :: YesodAuth m => Text -> Text -> AuthPlugin m
oauth2GitLab :: forall m. YesodAuth m => Text -> Text -> AuthPlugin m
oauth2GitLab = forall m.
YesodAuth m =>
URI -> [Text] -> Text -> Text -> AuthPlugin m
oauth2GitLabHostScopes URI
defaultHost [Text]
defaultScopes

oauth2GitLabHostScopes
  :: YesodAuth m => URI -> [Text] -> Text -> Text -> AuthPlugin m
oauth2GitLabHostScopes :: forall m.
YesodAuth m =>
URI -> [Text] -> Text -> Text -> AuthPlugin m
oauth2GitLabHostScopes URI
host [Text]
scopes Text
clientId Text
clientSecret =
  forall m.
YesodAuth m =>
Text -> OAuth2 -> FetchCreds m -> AuthPlugin m
authOAuth2 Text
pluginName OAuth2
oauth2 forall a b. (a -> b) -> a -> b
$ \Manager
manager OAuth2Token
token -> do
    (User Int
userId, ByteString
userResponse) <-
      forall a.
FromJSON a =>
Text -> Manager -> OAuth2Token -> URI -> IO (a, ByteString)
authGetProfile Text
pluginName Manager
manager OAuth2Token
token forall a b. (a -> b) -> a -> b
$ URI
host forall a. URIRef a -> ByteString -> URIRef a
`withPath` ByteString
"/api/v4/user"

    forall (f :: * -> *) a. Applicative f => a -> f a
pure
      Creds
        { credsPlugin :: Text
credsPlugin = Text
pluginName
        , credsIdent :: Text
credsIdent = String -> Text
T.pack forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show Int
userId
        , credsExtra :: [(Text, Text)]
credsExtra = OAuth2Token -> ByteString -> [(Text, Text)]
setExtra OAuth2Token
token ByteString
userResponse
        }
 where
  oauth2 :: OAuth2
oauth2 =
    OAuth2
      { oauth2ClientId :: Text
oauth2ClientId = Text
clientId
      , oauth2ClientSecret :: Maybe Text
oauth2ClientSecret = forall a. a -> Maybe a
Just Text
clientSecret
      , oauth2AuthorizeEndpoint :: URI
oauth2AuthorizeEndpoint =
          URI
host forall a. URIRef a -> ByteString -> URIRef a
`withPath` ByteString
"/oauth/authorize" forall a. URIRef a -> [(ByteString, ByteString)] -> URIRef a
`withQuery` [Text -> [Text] -> (ByteString, ByteString)
scopeParam Text
" " [Text]
scopes]
      , oauth2TokenEndpoint :: URI
oauth2TokenEndpoint = URI
host forall a. URIRef a -> ByteString -> URIRef a
`withPath` ByteString
"/oauth/token"
      , oauth2RedirectUri :: Maybe URI
oauth2RedirectUri = forall a. Maybe a
Nothing
      }