{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE OverloadedStrings #-} {-| Module : Snap.AtlassianConnect.HostRequest Description : Allows you to easily make requests from your Atlassian Connect addon to the Host Application (like Jira or Confluence). Copyright : (c) Robert Massioli, 2014-2017 License : APACHE-2 Maintainer : rmassaioli@atlassian.com Stability : experimental While writing Atlassian Connect applications you will often be in a situation where you want to query the Host Application directly in a trusted way. This may be because: * You are not making this request on behalf of a user. You are making it on behalf of your Addon. (Data ingestion etc.) * You cannot trust the information that the Customer has given you. For example: don't trust the customer to tell you if they are an admin or not. Go directly to the Host application for that. This module allows you to make HTTP requests to the host application and expect JSON responses. There are convinience methods for GET, POST and PUT requests which make up the majority of the requests that you are going to make. It is important to note that these requests are still restricted by the that you have asked for in your Atlassian Connect Descriptor. For an example of usage: look at the httpGetRequest function. -} module Snap.AtlassianConnect.HostRequest ( -- * Host (Product) Request Helpers hostRequest , hostGetRequest , hostPostRequest , hostPostRequestExtended , hostPutRequest , hostPutRequestExtended , StdMethod(..) , AC.ProductErrorResponse(..) -- * Request Modifiers , addHeader , setPostParams , setQueryParams , setBody , setBodyLazy , setJson ) where import Control.Applicative import Control.Applicative import qualified Control.Monad.IO.Class as MI import Control.Monad.State (get) import Data.Aeson import qualified Data.ByteString as B import qualified Data.ByteString.Char8 as BC import qualified Data.ByteString.Lazy as BL import Data.Connect.Descriptor as CD import Data.List (isPrefixOf) import qualified Data.Map as M import Data.Monoid 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 GHC.Generics import Network.Api.Support import Network.HTTP.Client import Network.HTTP.Client.TLS (tlsManagerSettings) import Network.HTTP.Types import Network.URI import qualified Snap.AtlassianConnect.Data as AC import qualified Snap.AtlassianConnect.Instances as AC import qualified Snap.AtlassianConnect.QueryStringHash as QSH import qualified Snap.AtlassianConnect.NetworkCommon as AC import qualified Snap.AtlassianConnect.Tenant as AC import qualified Snap.Snaplet as SS import qualified Web.JWT as JWT -- | This is a convinience method that calls 'hostRequest' as a GET method. -- -- Here is an example of it being used to make a call for user details: -- -- > jiraUserDetailsResponse <- hostGetRequest myConnectTenant Nothing "/rest/api/2/user" [("username", Just "admin")] mempty -- -- This example assumes that you are using the OverloadedStrings LANGUAGE pragma and that you don't need to modify the request. -- You might want to might want to modify the request for multiple reasons. Too add proxy details for example. hostGetRequest :: FromJSON a => AC.Tenant -> Maybe AC.AccessToken -> B.ByteString -> [(B.ByteString, Maybe B.ByteString)] -> Endo Request -> SS.Handler b AC.Connect (Either AC.ProductErrorResponse a) hostGetRequest = hostRequestWithContent GET -- | This is a convinience method that calls 'hostRequest' as a POST method and requires that the -- resource returns content. hostPostRequest :: FromJSON a => AC.Tenant -> Maybe AC.AccessToken -> B.ByteString -> [(B.ByteString, Maybe B.ByteString)] -> Endo Request -> SS.Handler b AC.Connect (Either AC.ProductErrorResponse a) hostPostRequest = hostRequestWithContent POST -- | This is the same method as hostPostRequest except that if HTTP 204 No Content is returned then -- you will get nothing instead of an error. hostPostRequestExtended :: FromJSON a => AC.Tenant -> Maybe AC.AccessToken -> B.ByteString -> [(B.ByteString, Maybe B.ByteString)] -> Endo Request -> SS.Handler b AC.Connect (Either AC.ProductErrorResponse (Maybe a)) hostPostRequestExtended = hostRequest POST -- | This is a convinience method that calls 'hostRequest' as a PUT method. hostPutRequest :: FromJSON a => AC.Tenant -> Maybe AC.AccessToken -> B.ByteString -> [(B.ByteString, Maybe B.ByteString)] -> Endo Request -> SS.Handler b AC.Connect (Either AC.ProductErrorResponse a) hostPutRequest = hostRequestWithContent PUT -- | This is the same method as hostPutRequest except that if HTTP 204 No Content is returned then -- you will get nothing instead of an error. hostPutRequestExtended :: FromJSON a => AC.Tenant -> Maybe AC.AccessToken -> B.ByteString -> [(B.ByteString, Maybe B.ByteString)] -> Endo Request -> SS.Handler b AC.Connect (Either AC.ProductErrorResponse (Maybe a)) hostPutRequestExtended = hostRequest PUT hostRequestWithContent :: FromJSON a => StdMethod -> AC.Tenant -> Maybe AC.AccessToken -> B.ByteString -> [(B.ByteString, Maybe B.ByteString)] -> Endo Request -> SS.Handler b AC.Connect (Either AC.ProductErrorResponse a) hostRequestWithContent httpMethod tenant accessToken productRelativeUrl queryParams modifications = errorNoContent <$> hostRequest httpMethod tenant accessToken productRelativeUrl queryParams modifications errorNoContent :: Either AC.ProductErrorResponse (Maybe a) -> Either AC.ProductErrorResponse a errorNoContent (Left x) = Left x errorNoContent (Right Nothing) = Left (AC.ProductErrorResponse 204 "We expected to get content back from this resource but instead we recieved no content.") errorNoContent (Right (Just x)) = Right x -- | As an Atlassian Connect application you will want to make requests of the Host Applicaiton (JIRA / Confluence) -- so that you can get important information. This function lets you do so by doing most of the heavy lifting of -- having to create a JWT token and a Query String Hash. It also asserts that you intended to get a JSON response. -- You should use this method or the helper methods whenever you want to make requests of the host application. hostRequest :: FromJSON a => StdMethod -> AC.Tenant -> Maybe AC.AccessToken -> B.ByteString -> [(B.ByteString, Maybe B.ByteString)] -> Endo Request -> SS.Handler b AC.Connect (Either AC.ProductErrorResponse (Maybe a)) hostRequest standardHttpMethod tenant Nothing productRelativeUrl queryParams requestModifications = do currentTime <- MI.liftIO P.getPOSIXTime pluginKey' <- fmap (CD.pluginKey . AC.connectPlugin) get case generateJWTToken pluginKey' currentTime (AC.sharedSecret tenant) standardHttpMethod productBaseUrl url of Nothing -> return . Left $ AC.ProductErrorResponse 500 "Failed to generate a JWT token to make the request. The request was never made: server error." (Just signature) -> MI.liftIO $ runRequest tlsManagerSettings standardHttpMethod url ( addHeader ("Accept", "application/json") <> addHeader ("Authorization", jwtPrefix `B.append` T.encodeUtf8 signature) <> requestModifications ) (basicResponder AC.responder) where jwtPrefix :: B.ByteString jwtPrefix = BC.pack "JWT " url = T.decodeUtf8 $ BC.pack productBaseUrlString `B.append` productRelativeUrl `B.append` renderQuery True queryParams productBaseUrlString = show productBaseUrl productBaseUrl = AC.getURI . AC.baseUrl $ tenant hostRequest standardHttpMethod tenant (Just (AC.AccessToken accessToken)) productRelativeUrl queryParams requestModifications = do MI.liftIO $ putStrLn $ "Using bearer token: " ++ show accessToken MI.liftIO $ runRequest tlsManagerSettings standardHttpMethod url ( addHeader ("Accept", "application/json") <> addHeader ("Authorization", bearerPrefix `B.append` T.encodeUtf8 accessToken) <> requestModifications ) (basicResponder AC.responder) where bearerPrefix :: B.ByteString bearerPrefix = BC.pack "Bearer " url = T.decodeUtf8 $ BC.pack productBaseUrlString `B.append` productRelativeUrl `B.append` renderQuery True queryParams productBaseUrlString = show . AC.getURI . AC.baseUrl $ tenant generateJWTToken :: CD.PluginKey -> P.POSIXTime -> T.Text -> StdMethod -> URI -> T.Text -> Maybe T.Text generateJWTToken pluginKey' fromTime sharedSecret' method' ourURL requestURL = do queryStringHash <- QSH.createQueryStringHash method' ourURL requestURL return $ JWT.encodeSigned JWT.HS256 (JWT.secret sharedSecret') (createClaims pluginKey' fromTime queryStringHash) createClaims :: CD.PluginKey -> P.POSIXTime -> T.Text -> JWT.JWTClaimsSet createClaims (CD.PluginKey pluginKey) fromTime queryStringHash = JWT.JWTClaimsSet { JWT.iss = JWT.stringOrURI pluginKey , JWT.iat = JWT.numericDate fromTime , JWT.exp = JWT.numericDate expiryTime , JWT.sub = Nothing , JWT.aud = Nothing , JWT.nbf = Nothing , JWT.jti = Nothing , JWT.unregisteredClaims = M.fromList [("qsh", String queryStringHash)] } where expiryTime :: P.POSIXTime expiryTime = fromTime + timeUnitToDiffTime expiryPeriod -- Our default expiry period when talking to the host product directly expiryPeriod :: Minute expiryPeriod = 1 -- Wrapper around another function setPostParams :: [(B.ByteString, B.ByteString)] -> Endo Request setPostParams = setUrlEncodedBody