{-# LANGUAGE OverloadedStrings #-}

{-|
Module      : Snap.AtlassianConnect.OAuth
Description : Allows you to impersonate users inside an Atlassian Product (like JIRA or Confluence).
Copyright   : (c) Robert Massioli, 2017
License     : APACHE-2
Maintainer  : rmassaioli@atlassian.com
Stability   : experimental

By default, all HTTP requests that your add-on makes to an Atlassian application (like JIRA or Confluence) will
be performed as your add-on user. For example, if your add-on service makes a HTTP request to comment on a JIRA 
issue then the comment will be made as your add-on. However, if your addon requests the "ACT_AS_USER" scope then
is is capable of using the OAuth service to generate an "access token" for a particular user on a tenant. This
access token can be used to make make HTTP requests from your add-on service to an Atlassian product as a user
inside that product. This allows you to make HTTP requests that can impersonate users on a given instance.

Using our previous example, if you generated an access token for the user "Bob" and then made the same request,
but with that new access token, then the comment made on the issue would appear to come from Bob.

You can read more about access token on the <https://developer.atlassian.com/cloud/jira/platform/oauth-2-jwt-bearer-token-authorization-grant-type/ official documentation>.
-}
module Snap.AtlassianConnect.OAuth 
    ( requestAccessToken
    , AC.AccessTokenResponse(..)
    , AC.AccessToken
    , AC.AccessTokenType(..)
    ) where

import           Data.Aeson
import qualified Data.ByteString.Char8                 as BSC
import qualified Data.ByteString.Lazy                  as BL
import qualified Data.Connect.Descriptor               as D
import           Data.List                             (isPrefixOf)
import qualified Data.Map                              as M
import qualified Data.Text                             as T
import qualified Data.Text.Encoding                    as T
import qualified Data.Time.Clock.POSIX                 as P
import           Data.Time.Units                       (Minute)
import           Data.TimeUnitUTC
import           Network.Api.Support
import           Network.HTTP.Client
import           Network.HTTP.Client.TLS               (tlsManagerSettings)
import           Network.HTTP.Types
import           Network.URI
import           Snap.AtlassianConnect.AtlassianTypes
import qualified Snap.AtlassianConnect.Data            as AC
import qualified Snap.AtlassianConnect.Instances       as AC
import qualified Snap.AtlassianConnect.NetworkCommon   as AC
import qualified Snap.AtlassianConnect.Tenant          as AC
import qualified Web.JWT                               as JWT

-- | Request an access token for a tenant and user with the requested scopes. 
-- 
-- This token will allow you to post subsequent HTTP requests using the Snap.AtlassianConnect.HostRequest module
-- as an impersonated user.
--
-- The access token that is returned should be reused as much as possible in order to avoid hitting rate limits 
-- from the token generation service. Each token is specific to the tenant, user and scopes that
-- it was created for. This means that the token reuse must be tenant, user and scopes specific.
requestAccessToken 
    :: AC.Tenant -- ^ The tenant to generate the Access Token for.
    -> UserKey -- ^ The user key of the user on the tenant that should be impersonated.
    -> Maybe [D.ProductScope] -- ^ The collection of scopes that will be used for impersonation. Providing none requests all scopes that the add-on provides.
    -> IO (Either AC.ProductErrorResponse (Maybe AC.AccessTokenResponse)) -- ^ Returns either a HTTP error or the result of attempting to parse the AccessTokenResponse.
requestAccessToken tenant userKey possibleScopes = do
    potentialAssertion <- generateJWTAssertion tenant userKey
    case potentialAssertion of
        Nothing -> return . Right $ Nothing
        Just assertion ->
            runRequest tlsManagerSettings POST url
                ( addHeader ("Host", "auth.atlassian.io")
                <> addHeader ("Accept", "application/json")
                <> addHeader ("Content-Type", "application/x-www-form-urlencoded")
                <> setBody (renderSimpleQuery False (formParams assertion))
                )
                (basicResponder AC.responder)
    where
        url = authBaseUrl `T.append` "/oauth2/token"

        formParams :: T.Text -> [(BSC.ByteString, BSC.ByteString)]
        formParams assertion = 
            [ ("grant_type", "urn:ietf:params:oauth:grant-type:jwt-bearer")
            , ("assertion", T.encodeUtf8 assertion)
            ] ++ scopeParam

        scopeParam = case possibleScopes of
            Nothing -> []
            Just scopes -> (: []) . (,) "scope" . BSC.intercalate " " . fmap printScope . filter ((/=) D.ActAsUser) $ scopes

printScope :: D.ProductScope -> BSC.ByteString 
printScope D.Read         = "READ"
printScope D.Write        = "WRITE"
printScope D.Delete       = "DELETE"
printScope D.ProjectAdmin = "PROJECT_ADMIN"
printScope D.SpaceAdmin   = "SPACE_ADMIN"
printScope D.Admin        = "ADMIN"
printScope D.ActAsUser    = "ACT_AS_USER"

generateJWTAssertion :: AC.Tenant -> UserKey -> IO (Maybe T.Text)
generateJWTAssertion tenant userKey = do
    currentTime <- P.getPOSIXTime
    case generateAssertionClaims currentTime tenant userKey of
        Nothing -> return Nothing
        Just claims -> return . Just $ JWT.encodeSigned JWT.HS256 jwtSecret claims
    where
        jwtSecret = JWT.secret . AC.sharedSecret $ tenant

-- These claims are documented here: https://developer.atlassian.com/cloud/jira/platform/oauth-2-jwt-bearer-token-authorization-grant-type/
{-
`iss`	String	the issuer of the claim. For example: `urn:atlassian:connect:clientid:{oauthClientId}`
`sub`	String	The subject of the token. For example: `urn:atlassian:connect:userkey:{userkey of the user to run services on behalf of}` **NOTE:** The `userkey` is different from the `username`. For example, to get the `userkey` for username alex use the REST endpoint `/rest/api/2/user?username=alex` in JIRA or `/rest/api/user?username=alex` in Confluence.
`tnt`	String	The instance the add-on is installed on. For example: `https://{your-instance}.atlassian.net`
`aud`	String	The Atlassian authentication server: `https://auth.atlassian.io`
`iat`	Long	Issue time in seconds since the epoch UTC.
`exp`	Long	Expiry time in seconds since the epoch UTC. Must be no later that 60 seconds in the future.
-}
generateAssertionClaims :: P.POSIXTime -> AC.Tenant -> UserKey -> Maybe JWT.JWTClaimsSet
generateAssertionClaims fromTime tenant userKey = do
    oid <- AC.oauthClientId tenant
    return JWT.JWTClaimsSet
        { JWT.iss = JWT.stringOrURI $ "urn:atlassian:connect:clientid:" `T.append` oid
        , JWT.sub = JWT.stringOrURI $ "urn:atlassian:connect:userkey:" `T.append` userKey
        , JWT.aud = Left <$> JWT.stringOrURI authBaseUrl
        , JWT.iat = JWT.numericDate fromTime
        , JWT.exp = JWT.numericDate expiryTime
        , JWT.nbf = Nothing
        , JWT.jti = Nothing
        , JWT.unregisteredClaims = M.fromList [("tnt", String . T.pack $ tenantBaseUrlString)]
        }
    where
        tenantBaseUrlString = show . AC.getURI . AC.baseUrl $ tenant

        expiryTime :: P.POSIXTime
        expiryTime = fromTime + timeUnitToDiffTime expiryPeriod

        -- One minute is the maximum expiry time for this token
        expiryPeriod :: Minute
        expiryPeriod = 1

authBaseUrl :: T.Text 
authBaseUrl = "https://auth.atlassian.io"