server: add support for webhook connection expiration (#4196)

* add expiry time to webhook user info

This also adds an optional message to webhook errors: if we fail to
parse an expiry time, we will log a warning with the parse error.

* refactored Auth

This change had one main goal: put in common all expiry time
extraction code between the JWT and WebHook parts of the
code. Furthermore, this change also moves all WebHook specific code to
its own module, similarly to what is done for JWT.

* Remove dependency on string-conversions in favor of text-conversions

string-conversions silently uses UTF8 instead of being explicit about
it, and it uses lenientDecode when decoding ByteStrings when it’s
usually better to reject invalid UTF8 input outright. text-conversions
solves both those problems.

Co-authored-by: Alexis King <lexi.lambda@gmail.com>
This commit is contained in:
Antoine Leblanc 2020-04-03 01:00:13 +01:00 committed by GitHub
parent 8bcff193d9
commit 5b54f9d766
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
15 changed files with 345 additions and 166 deletions

View File

@ -108,6 +108,12 @@ Read more about this command in the [docs](https://hasura.io/docs/1.0/graphql/ma
(close #1156) (#3760)
### Expiration of connections authenticated by WebHooks
When using webhooks to authenticate incoming requests to the GraphQL engine server, it is now possible to specify an expiration time; the connection to the server will be automatically closed if it's still running when the expiration delay is expired.
Read more about it in the [docs](https://hasura.io/docs/1.0/graphql/manual/auth/authentication/webhook.html).
### Bug fixes and improvements
- server: check expression in update permissions (close #384) (rfc #3750) (#3804)
- console: show pre-release update notifications with opt out option (#3888)

View File

@ -110,6 +110,40 @@ You should send the ``X-Hasura-*`` "session variables" to your permission rules
.. note::
All values should be ``String``. They will be converted to the right type automatically.
There is no default timeout on the resulting connection. You can optionally add one; to do so, you need to return either:
* a ``Cache-Control`` variable, modeled on the `Cache-Control HTTP Header <https://developer.mozilla.org/en-US/docs/Web/HTTP/Headers/Cache-Control>`__, to specify a **relative** expiration time, in seconds.
.. code-block:: http
HTTP/1.1 200 OK
Content-Type: application/json
{
"X-Hasura-User-Id": "26",
"X-Hasura-Role": "user",
"X-Hasura-Is-Owner": "false",
"Cache-Control": "max-age=600"
}
* an ``Expires`` variable, modeled on the `Expires HTTP Header <https://developer.mozilla.org/en-US/docs/Web/HTTP/Headers/Expires>`__, to specify an **absolute** expiration time. The expected format is ``"%a, %d %b %Y %T GMT"``.
.. code-block:: http
HTTP/1.1 200 OK
Content-Type: application/json
{
"X-Hasura-User-Id": "27",
"X-Hasura-Role": "user",
"X-Hasura-Is-Owner": "false",
"Expires": "Mon, 30 Mar 2020 13:25:18 GMT"
}
Failure
+++++++
If you want to deny the GraphQL request, return a ``401 Unauthorized`` exception.

View File

@ -126,7 +126,6 @@ library
-- String related
, case-insensitive
, string-conversions
, text-conversions
-- Http client
@ -249,6 +248,7 @@ library
, Hasura.Incremental.Internal.Rule
, Hasura.Server.Auth.JWT
, Hasura.Server.Auth.WebHook
, Hasura.Server.Middleware
, Hasura.Server.Cors
, Hasura.Server.CheckUpdates
@ -378,6 +378,7 @@ library
, Data.Sequence.NonEmpty
, Data.TByteString
, Data.Text.Extended
, Data.Parser.Expires
, Hasura.SQL.DML
, Hasura.SQL.Error

View File

@ -0,0 +1,17 @@
module Data.Parser.Expires
( parseExpirationTime
) where
import Control.Monad.Except
import Data.Text.Conversions
import Data.Time.Clock
import Data.Time.Format (defaultTimeLocale, parseTimeM)
import Hasura.Prelude
-- | Extracts an absolute expiration time from a Expires header.
parseExpirationTime :: MonadError String m => Text -> m UTCTime
parseExpirationTime = fromText
>>> parseTimeM True defaultTimeLocale "%a, %d %b %Y %T GMT"
>>> (`onNothing` throwError "Value of Expires header is not a valid timestamp")

View File

@ -23,12 +23,12 @@ module Hasura.GraphQL.Execute
import Control.Exception (try)
import Control.Lens
import Data.Has
import Data.Text.Conversions
import qualified Data.Aeson as J
import qualified Data.CaseInsensitive as CI
import qualified Data.HashMap.Strict as Map
import qualified Data.HashSet as Set
import qualified Data.String.Conversions as CS
import qualified Data.Text as T
import qualified Language.GraphQL.Draft.Syntax as G
import qualified Network.HTTP.Client as HTTP
@ -424,5 +424,5 @@ execRemoteGQ reqId userInfo reqHdrs q rsi opDef = do
HTTP.HttpExceptionRequest _req content -> throw500 $ T.pack . show $ content
HTTP.InvalidUrlException _url reason -> throw500 $ T.pack . show $ reason
userInfoToHdrs = map (\(k, v) -> (CI.mk $ CS.cs k, CS.cs v)) $
userInfoToList userInfo
userInfoToHdrs = userInfoToList userInfo
& map (CI.mk . unUTF8 . fromText *** unUTF8 . fromText)

View File

@ -82,7 +82,7 @@ data WSConnState
= CSNotInitialised !WsHeaders
| CSInitError !Text
-- headers from the client (in conn params) to forward to the remote schema
-- and JWT expiry time if any
-- and token expiry time if any
| CSInitialised !UserInfo !(Maybe TC.UTCTime) ![H.Header]
data WSConnData
@ -153,7 +153,7 @@ $(J.deriveToJSON
data WsConnInfo
= WsConnInfo
{ _wsciWebsocketId :: !WS.WSId
, _wsciJwtExpiry :: !(Maybe TC.UTCTime)
, _wsciTokenExpiry :: !(Maybe TC.UTCTime)
, _wsciMsg :: !(Maybe Text)
} deriving (Show, Eq)
$(J.deriveToJSON (J.aesonDrop 5 J.snakeCase) ''WsConnInfo)
@ -214,7 +214,7 @@ onConn (L.Logger logger) corsPolicy wsId requestHead = do
sendMsg wsConn SMConnKeepAlive
sleep $ seconds 5
jwtExpiryHandler wsConn = do
tokenExpiryHandler wsConn = do
expTime <- liftIO $ STM.atomically $ do
connState <- STM.readTVar $ (_wscUser . WS.getData) wsConn
case connState of
@ -233,7 +233,7 @@ onConn (L.Logger logger) corsPolicy wsId requestHead = do
<*> pure errType
let acceptRequest = WS.defaultAcceptRequest
{ WS.acceptSubprotocol = Just "graphql-ws"}
return $ Right $ WS.AcceptWith connData acceptRequest keepAliveAction jwtExpiryHandler
return $ Right $ WS.AcceptWith connData acceptRequest keepAliveAction tokenExpiryHandler
reject qErr = do
logger $ mkWsErrorLog Nothing (WsConnInfo wsId Nothing Nothing) (ERejected qErr)
@ -508,12 +508,12 @@ logWSEvent
=> L.Logger L.Hasura -> WSConn -> WSEvent -> m ()
logWSEvent (L.Logger logger) wsConn wsEv = do
userInfoME <- liftIO $ STM.readTVarIO userInfoR
let (userVarsM, jwtExpM) = case userInfoME of
CSInitialised userInfo jwtM _ -> ( Just $ userVars userInfo
, jwtM
)
_ -> (Nothing, Nothing)
liftIO $ logger $ WSLog logLevel $ WSLogInfo userVarsM (WsConnInfo wsId jwtExpM Nothing) wsEv
let (userVarsM, tokenExpM) = case userInfoME of
CSInitialised userInfo tokenM _ -> ( Just $ userVars userInfo
, tokenM
)
_ -> (Nothing, Nothing)
liftIO $ logger $ WSLog logLevel $ WSLogInfo userVarsM (WsConnInfo wsId tokenExpM Nothing) wsEv
where
WSConnData userInfoR _ _ = WS.getData wsConn
wsId = WS.getWSId wsConn
@ -541,7 +541,7 @@ onConnInit logger manager wsConn authMode connParamsM = do
let !initErr = CSInitError $ qeError e
liftIO $ do
$assertNFHere initErr -- so we don't write thunks to mutable vars
STM.atomically $ STM.writeTVar (_wscUser $ WS.getData wsConn) initErr
STM.atomically $ STM.writeTVar (_wscUser $ WS.getData wsConn) initErr
let connErr = ConnErrMsg $ qeError e
logWSEvent logger wsConn $ EConnErr connErr

View File

@ -6,6 +6,7 @@ module Hasura.Prelude
, onJust
, onLeft
, choice
, afold
, bsToTxt
, txtToBs
, spanMaybeM
@ -42,9 +43,10 @@ import Data.HashSet as M (HashSet)
import Data.List as M (find, findIndex, foldl', group,
intercalate, intersect, lookup, sort,
sortBy, sortOn, union, unionBy, (\\))
import Data.List.NonEmpty as M (NonEmpty(..))
import Data.List.NonEmpty as M (NonEmpty (..))
import Data.Maybe as M (catMaybes, fromMaybe, isJust, isNothing,
listToMaybe, mapMaybe, maybeToList)
import Data.Monoid as M (getAlt)
import Data.Ord as M (comparing)
import Data.Semigroup as M (Semigroup (..))
import Data.Sequence as M (Seq)
@ -52,13 +54,13 @@ import Data.String as M (IsString)
import Data.Text as M (Text)
import Data.These as M (These (..), fromThese, mergeThese,
mergeTheseWith, these)
import Data.Time.Clock.Units
import Data.Traversable as M (for)
import Data.Word as M (Word64)
import GHC.Generics as M (Generic)
import Prelude as M hiding (fail, init, lookup)
import Test.QuickCheck.Arbitrary.Generic as M
import Text.Read as M (readEither, readMaybe)
import Data.Time.Clock.Units
import qualified Data.ByteString as B
import qualified Data.HashMap.Strict as Map
@ -86,6 +88,9 @@ onLeft e f = either f return e
choice :: (Alternative f) => [f a] -> f a
choice = asum
afold :: (Foldable t, Alternative f) => t a -> f a
afold = getAlt . foldMap pure
bsToTxt :: B.ByteString -> Text
bsToTxt = TE.decodeUtf8With TE.lenientDecode

View File

@ -1,11 +1,13 @@
{-# LANGUAGE RecordWildCards #-}
module Hasura.Server.Auth
( getUserInfo
, getUserInfoWithExpTime
, AuthMode(..)
, AuthMode (..)
, mkAuthMode
, AdminSecret (..)
, AuthHookType(..)
-- WebHook related
, AuthHookType (..)
, AuthHookG (..)
, AuthHook
-- JWT related
@ -19,33 +21,26 @@ module Hasura.Server.Auth
) where
import Control.Concurrent.Extended (forkImmortal)
import Control.Exception (try)
import Control.Lens
import Data.Aeson
import Data.IORef (newIORef)
import Data.Time.Clock (UTCTime)
import Hasura.Server.Version (HasVersion)
import qualified Data.Aeson as J
import qualified Data.ByteString.Lazy as BL
import qualified Data.HashMap.Strict as Map
import qualified Data.Text as T
import qualified Network.HTTP.Client as H
import qualified Network.HTTP.Types as N
import qualified Network.Wreq as Wreq
import Hasura.HTTP
import Hasura.Logging
import Hasura.Prelude
import Hasura.RQL.Types
import Hasura.Server.Auth.JWT
import Hasura.Server.Logging
import Hasura.Server.Auth.WebHook
import Hasura.Server.Utils
-- | Typeclass representing the @UserInfo@ authorization and resolving effect
class (Monad m) => UserAuthentication m where
resolveUserInfo
:: (HasVersion)
:: HasVersion
=> Logger Hasura
-> H.Manager
-> [N.Header]
@ -57,22 +52,6 @@ newtype AdminSecret
= AdminSecret { getAdminSecret :: T.Text }
deriving (Show, Eq)
data AuthHookType
= AHTGet
| AHTPost
deriving (Eq)
instance Show AuthHookType where
show AHTGet = "GET"
show AHTPost = "POST"
data AuthHookG a b
= AuthHookG
{ ahUrl :: !a
, ahType :: !b
} deriving (Show, Eq)
type AuthHook = AuthHookG T.Text AuthHookType
data AuthMode
= AMNoAuth
@ -103,13 +82,13 @@ mkAuthMode mAdminSecret mWebHook mJwtSecret mUnAuthRole httpManager logger =
jwtCtx <- mkJwtCtx jwtConf httpManager logger
return $ AMAdminSecretAndJWT key jwtCtx mUnAuthRole
(Nothing, Just _, Nothing) -> throwError $
(Nothing, Just _, Nothing) -> throwError $
"Fatal Error : --auth-hook (HASURA_GRAPHQL_AUTH_HOOK)" <> requiresAdminScrtMsg
(Nothing, Nothing, Just _) -> throwError $
(Nothing, Nothing, Just _) -> throwError $
"Fatal Error : --jwt-secret (HASURA_GRAPHQL_JWT_SECRET)" <> requiresAdminScrtMsg
(Nothing, Just _, Just _) -> throwError
(Nothing, Just _, Just _) -> throwError
"Fatal Error: Both webhook and JWT mode cannot be enabled at the same time"
(Just _, Just _, Just _) -> throwError
(Just _, Just _, Just _) -> throwError
"Fatal Error: Both webhook and JWT mode cannot be enabled at the same time"
where
requiresAdminScrtMsg =
@ -161,86 +140,7 @@ mkJwtCtx JWTConfig{..} httpManager logger = do
JFEExpiryParseError _ _ -> return Nothing
-- | Form the 'UserInfo' from the response from webhook
mkUserInfoFromResp
:: (MonadIO m, MonadError QErr m)
=> Logger Hasura
-> T.Text
-> N.StdMethod
-> N.Status
-> BL.ByteString
-> m UserInfo
mkUserInfoFromResp logger url method statusCode respBody
| statusCode == N.status200 =
case eitherDecode respBody of
Left e -> do
logError
throw500 $ "Invalid response from authorization hook: " <> T.pack e
Right rawHeaders -> getUserInfoFromHdrs rawHeaders
| statusCode == N.status401 = do
logError
throw401 "Authentication hook unauthorized this request"
| otherwise = do
logError
throw500 "Invalid response from authorization hook"
where
getUserInfoFromHdrs rawHeaders = do
let usrVars = mkUserVars $ Map.toList rawHeaders
case roleFromVars usrVars of
Nothing -> do
logError
throw500 "missing x-hasura-role key in webhook response"
Just rn -> do
logWebHookResp LevelInfo Nothing
return $ mkUserInfo rn usrVars
logError =
logWebHookResp LevelError $ Just respBody
logWebHookResp logLevel mResp =
unLogger logger $ WebHookLog logLevel (Just statusCode)
url method Nothing $ fmap (bsToTxt . BL.toStrict) mResp
userInfoFromAuthHook
:: (HasVersion, MonadIO m, MonadError QErr m)
=> Logger Hasura
-> H.Manager
-> AuthHook
-> [N.Header]
-> m UserInfo
userInfoFromAuthHook logger manager hook reqHeaders = do
res <- liftIO $ try $ bool withGET withPOST isPost
resp <- either logAndThrow return res
let status = resp ^. Wreq.responseStatus
respBody = resp ^. Wreq.responseBody
mkUserInfoFromResp logger urlT method status respBody
where
mkOptions = wreqOptions manager
AuthHookG urlT ty = hook
isPost = case ty of
AHTPost -> True
AHTGet -> False
method = bool N.GET N.POST isPost
withGET = Wreq.getWith (mkOptions filteredHeaders) $
T.unpack urlT
contentType = ("Content-Type", "application/json")
postHdrsPayload = J.toJSON $ Map.fromList $ hdrsToText reqHeaders
withPOST = Wreq.postWith (mkOptions [contentType]) (T.unpack urlT) $
object ["headers" J..= postHdrsPayload]
logAndThrow err = do
unLogger logger $
WebHookLog LevelError Nothing urlT method
(Just $ HttpException err) Nothing
throw500 "Internal Server Error"
filteredHeaders = flip filter reqHeaders $ \(n, _) ->
n `notElem` commonClientHeadersIgnored
getUserInfo
:: (HasVersion, MonadIO m, MonadError QErr m)
@ -271,10 +171,10 @@ getUserInfoWithExpTime logger manager rawHeaders = \case
AMAdminSecretAndHook accKey hook ->
whenAdminSecretAbsent accKey $
withNoExpTime $ userInfoFromAuthHook logger manager hook rawHeaders
userInfoFromAuthHook logger manager hook rawHeaders
AMAdminSecretAndJWT accKey jwtSecret unAuthRole ->
whenAdminSecretAbsent accKey (processJwt jwtSecret rawHeaders unAuthRole)
whenAdminSecretAbsent accKey $ processJwt jwtSecret rawHeaders unAuthRole
where
-- when admin secret is absent, run the action to retrieve UserInfo, otherwise

View File

@ -14,22 +14,23 @@ module Hasura.Server.Auth.JWT
import Control.Exception (try)
import Control.Lens
import Control.Monad (when)
import Control.Monad.Trans.Maybe
import Data.IORef (IORef, readIORef, writeIORef)
import Data.List (find)
import Data.Parser.CacheControl (parseMaxAge)
import Data.Time.Clock (NominalDiffTime, UTCTime, diffUTCTime,
getCurrentTime)
import Data.Time.Format (defaultTimeLocale, parseTimeM)
import GHC.AssertNF
import Network.URI (URI)
import Data.Parser.CacheControl
import Data.Parser.Expires
import Hasura.HTTP
import Hasura.Logging (Hasura, LogLevel (..), Logger (..))
import Hasura.Prelude
import Hasura.RQL.Types
import Hasura.Server.Auth.JWT.Internal (parseHmacKey, parseRsaKey)
import Hasura.Server.Auth.JWT.Logging
import Hasura.Server.Utils (fmapL, getRequestHeader, userRoleHeader)
import Hasura.Server.Utils (getRequestHeader, userRoleHeader)
import Hasura.Server.Version (HasVersion)
import qualified Control.Concurrent.Extended as C
@ -41,7 +42,6 @@ import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Lazy.Char8 as BLC
import qualified Data.CaseInsensitive as CI
import qualified Data.HashMap.Strict as Map
import qualified Data.String.Conversions as CS
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Network.HTTP.Client as HTTP
@ -101,7 +101,7 @@ defaultClaimNs = "https://hasura.io/jwt/claims"
-- | An action that refreshes the JWK at intervals in an infinite loop.
jwkRefreshCtrl
:: (HasVersion)
:: HasVersion
=> Logger Hasura
-> HTTP.Manager
-> URI
@ -114,7 +114,7 @@ jwkRefreshCtrl logger manager url ref time = liftIO $ do
res <- runExceptT $ updateJwkRef logger manager url ref
mTime <- either (const $ logNotice >> return Nothing) return res
-- if can't parse time from header, defaults to 1 min
let delay = maybe (minutes 1) (fromUnits) mTime
let delay = maybe (minutes 1) fromUnits mTime
C.sleep delay
where
logNotice = do
@ -155,26 +155,9 @@ updateJwkRef (Logger logger) manager url jwkRef = do
writeIORef jwkRef jwkset
-- first check for Cache-Control header to get max-age, if not found, look for Expires header
let cacheHeader = resp ^? Wreq.responseHeader "Cache-Control"
expiresHeader = resp ^? Wreq.responseHeader "Expires"
case cacheHeader of
Just header -> getTimeFromCacheControlHeader header
Nothing -> mapM getTimeFromExpiresHeader expiresHeader
runMaybeT $ timeFromCacheControl resp <|> timeFromExpires resp
where
getTimeFromExpiresHeader header = do
let maybeExpiry = parseTimeM True defaultTimeLocale timeFmt (CS.cs header)
expires <- maybe (logAndThrowInfo parseTimeErr) return maybeExpiry
currTime <- liftIO getCurrentTime
return $ diffUTCTime expires currTime
getTimeFromCacheControlHeader header =
case parseCacheControlHeader (bsToTxt header) of
Left e -> logAndThrowInfo e
Right maxAge -> return $ Just $ fromInteger maxAge
parseCacheControlHeader = fmapL (parseCacheControlErr . T.pack) . parseMaxAge
parseCacheControlErr e =
JFEExpiryParseError (Just e)
"Failed parsing Cache-Control header from JWK response. Could not find max-age or s-maxage"
@ -182,7 +165,13 @@ updateJwkRef (Logger logger) manager url jwkRef = do
JFEExpiryParseError Nothing
"Failed parsing Expires header from JWK response. Value of header is not a valid timestamp"
timeFmt = "%a, %d %b %Y %T GMT"
timeFromCacheControl resp = do
header <- afold $ bsToTxt <$> resp ^? Wreq.responseHeader "Cache-Control"
fromInteger <$> parseMaxAge header `onLeft` \err -> logAndThrowInfo $ parseCacheControlErr $ T.pack err
timeFromExpires resp = do
header <- afold $ bsToTxt <$> resp ^? Wreq.responseHeader "Expires"
expiry <- parseExpirationTime header `onLeft` const (logAndThrowInfo parseTimeErr)
diffUTCTime expiry <$> liftIO getCurrentTime
logAndThrowInfo :: (MonadIO m, MonadError JwkFetchError m) => JwkFetchError -> m a
logAndThrowInfo err = do

View File

@ -10,13 +10,13 @@ import Data.ASN1.Types (ASN1 (End, IntVal, Start),
ASN1ConstructionType (Sequence),
fromASN1)
import Data.Int (Int64)
import Data.Text.Conversions
import Hasura.Prelude
import Hasura.Server.Utils (fmapL)
import qualified Data.ByteString.Lazy as BL
import qualified Data.PEM as PEM
import qualified Data.String.Conversions as CS
import qualified Data.Text as T
import qualified Data.X509 as X509
@ -24,7 +24,7 @@ import qualified Data.X509 as X509
parseHmacKey :: T.Text -> Int64 -> Either T.Text JWK
parseHmacKey key size = do
let secret = CS.cs key
let secret = unUTF8 $ fromText key
err s = "Key size too small; should be atleast " <> show (s `div` 8) <> " characters"
if BL.length secret < size `div` 8
then Left . T.pack $ err size
@ -32,7 +32,7 @@ parseHmacKey key size = do
parseRsaKey :: T.Text -> Either T.Text JWK
parseRsaKey key = do
let res = fromRawPem (CS.cs key)
let res = fromRawPem (unUTF8 $ fromText key)
err e = "Could not decode PEM: " <> e
either (Left . err) pure res

View File

@ -0,0 +1,141 @@
module Hasura.Server.Auth.WebHook
( AuthHookType(..)
, AuthHookG (..)
, AuthHook
, userInfoFromAuthHook
) where
import Control.Exception (try)
import Control.Lens
import Control.Monad.Trans.Maybe
import Data.Aeson
import Data.Time.Clock (UTCTime, addUTCTime, getCurrentTime)
import Hasura.Server.Version (HasVersion)
import qualified Data.Aeson as J
import qualified Data.ByteString.Lazy as BL
import qualified Data.HashMap.Strict as Map
import qualified Data.Text as T
import qualified Network.HTTP.Client as H
import qualified Network.HTTP.Types as N
import qualified Network.Wreq as Wreq
import Data.Parser.CacheControl
import Data.Parser.Expires
import Hasura.HTTP
import Hasura.Logging
import Hasura.Prelude
import Hasura.RQL.Types
import Hasura.Server.Logging
import Hasura.Server.Utils
data AuthHookType
= AHTGet
| AHTPost
deriving (Eq)
instance Show AuthHookType where
show AHTGet = "GET"
show AHTPost = "POST"
data AuthHookG a b
= AuthHookG
{ ahUrl :: !a
, ahType :: !b
} deriving (Show, Eq)
type AuthHook = AuthHookG T.Text AuthHookType
hookMethod :: AuthHook -> N.StdMethod
hookMethod authHook = case ahType authHook of
AHTGet -> N.GET
AHTPost -> N.POST
-- | Makes an authentication request to the given AuthHook and returns
-- UserInfo parsed from the response, plus an expiration time if one
-- was returned.
userInfoFromAuthHook
:: (HasVersion, MonadIO m, MonadError QErr m)
=> Logger Hasura
-> H.Manager
-> AuthHook
-> [N.Header]
-> m (UserInfo, Maybe UTCTime)
userInfoFromAuthHook logger manager hook reqHeaders = do
resp <- (`onLeft` logAndThrow) =<< liftIO (try performHTTPRequest)
let status = resp ^. Wreq.responseStatus
respBody = resp ^. Wreq.responseBody
mkUserInfoFromResp logger (ahUrl hook) (hookMethod hook) status respBody
where
performHTTPRequest = do
let url = T.unpack $ ahUrl hook
mkOptions = wreqOptions manager
case ahType hook of
AHTGet -> do
let isCommonHeader = (`elem` commonClientHeadersIgnored)
filteredHeaders = filter (not . isCommonHeader . fst) reqHeaders
Wreq.getWith (mkOptions filteredHeaders) url
AHTPost -> do
let contentType = ("Content-Type", "application/json")
headersPayload = J.toJSON $ Map.fromList $ hdrsToText reqHeaders
Wreq.postWith (mkOptions [contentType]) url $ object ["headers" J..= headersPayload]
logAndThrow err = do
unLogger logger $
WebHookLog LevelError Nothing (ahUrl hook) (hookMethod hook)
(Just $ HttpException err) Nothing Nothing
throw500 $ "webhook authentication request failed"
mkUserInfoFromResp
:: (MonadIO m, MonadError QErr m)
=> Logger Hasura
-> T.Text
-> N.StdMethod
-> N.Status
-> BL.ByteString
-> m (UserInfo, Maybe UTCTime)
mkUserInfoFromResp (Logger logger) url method statusCode respBody
| statusCode == N.status200 =
case eitherDecode respBody of
Left e -> do
logError
throw500 $ "Invalid response from authorization hook: " <> T.pack e
Right rawHeaders -> getUserInfoFromHdrs rawHeaders
| statusCode == N.status401 = do
logError
throw401 "Authentication hook unauthorized this request"
| otherwise = do
logError
throw500 "Invalid response from authorization hook"
where
getUserInfoFromHdrs rawHeaders = do
let usrVars = mkUserVars $ Map.toList rawHeaders
case roleFromVars usrVars of
Nothing -> do
logError
throw500 "missing x-hasura-role key in webhook response"
Just rn -> do
logWebHookResp LevelInfo Nothing Nothing
expiration <- runMaybeT $ timeFromCacheControl rawHeaders <|> timeFromExpires rawHeaders
return (mkUserInfo rn usrVars, expiration)
logWebHookResp :: MonadIO m => LogLevel -> Maybe BL.ByteString -> Maybe T.Text -> m ()
logWebHookResp logLevel mResp message =
logger $ WebHookLog logLevel (Just statusCode)
url method Nothing (bsToTxt . BL.toStrict <$> mResp) message
logWarn message = logWebHookResp LevelWarn (Just respBody) (Just message)
logError = logWebHookResp LevelError (Just respBody) Nothing
timeFromCacheControl headers = do
header <- afold $ Map.lookup "Cache-Control" headers
duration <- parseMaxAge header `onLeft` \err -> logWarn (T.pack err) *> empty
addUTCTime (fromInteger duration) <$> liftIO getCurrentTime
timeFromExpires headers = do
header <- afold $ Map.lookup "Expires" headers
parseExpirationTime header `onLeft` \err -> logWarn (T.pack err) *> empty

View File

@ -103,6 +103,7 @@ data WebHookLog
, whlMethod :: !HTTP.StdMethod
, whlError :: !(Maybe HttpException)
, whlResponse :: !(Maybe T.Text)
, whlMessage :: !(Maybe T.Text)
} deriving (Show)
instance ToEngineLog WebHookLog Hasura where
@ -116,6 +117,7 @@ instance ToJSON WebHookLog where
, "method" .= show (whlMethod whl)
, "http_error" .= whlError whl
, "response" .= whlResponse whl
, "message" .= whlMessage whl
]

View File

@ -9,8 +9,8 @@ import Data.Aeson.TH
import qualified Data.ByteString.Lazy as BL
import Data.Char (isSpace)
import qualified Data.List as L
import qualified Data.String.Conversions as CS
import qualified Data.Text as T
import Data.Text.Conversions
import qualified Database.PG.Query as Q
import Hasura.Prelude
import qualified Hasura.RQL.Types.Error as RTE
@ -36,7 +36,7 @@ execPGDump b ci = do
output <- either throwException return eOutput
case output of
Left err ->
RTE.throw500 $ "error while executing pg_dump: " <> T.pack err
RTE.throw500 $ "error while executing pg_dump: " <> err
Right dump -> return dump
where
throwException :: (MonadError RTE.QErr m) => IOException -> m a
@ -45,8 +45,8 @@ execPGDump b ci = do
execProcess = do
(exitCode, stdOut, stdErr) <- readProcessWithExitCode "pg_dump" opts ""
return $ case exitCode of
ExitSuccess -> Right $ CS.cs (clean stdOut)
ExitFailure _ -> Left $ CS.cs stdErr
ExitSuccess -> Right $ unUTF8 $ convertText (clean stdOut)
ExitFailure _ -> Left $ toText stdErr
connString = T.unpack $ bsToTxt $ Q.pgConnString $ Q.ciDetails ci
opts = connString : "--encoding=utf8" : prbOpts b

View File

@ -153,7 +153,7 @@ class TestJWTBasic():
'x-hasura-default-role': 'user',
'x-hasura-allowed-roles': ['user'],
})
exp = datetime.now() - timedelta(minutes=1)
exp = datetime.utcnow() - timedelta(minutes=1)
self.claims['exp'] = round(exp.timestamp())
token = jwt.encode(self.claims, hge_ctx.hge_jwt_key, algorithm='RS512').decode('utf-8')
@ -239,7 +239,7 @@ class TestJWTBasic():
self.dir = 'queries/graphql_query/permissions'
with open(self.dir + '/user_select_query_unpublished_articles.yaml') as c:
self.conf = yaml.safe_load(c)
curr_time = datetime.now()
curr_time = datetime.utcnow()
exp_time = curr_time + timedelta(hours=1)
self.claims = {
'sub': '1234567890',
@ -274,7 +274,7 @@ def gen_rsa_key():
class TestSubscriptionJwtExpiry(object):
def test_jwt_expiry(self, hge_ctx, ws_client):
curr_time = datetime.now()
curr_time = datetime.utcnow()
self.claims = {
'sub': '1234567890',
'name': 'John Doe',
@ -353,7 +353,7 @@ class TestJwtAudienceCheck():
self.dir = 'queries/graphql_query/permissions'
with open(self.dir + '/user_select_query_unpublished_articles.yaml') as c:
self.conf = yaml.safe_load(c)
curr_time = datetime.now()
curr_time = datetime.utcnow()
exp_time = curr_time + timedelta(hours=1)
self.claims = {
'sub': '1234567890',
@ -425,7 +425,7 @@ class TestJwtIssuerCheck():
self.dir = 'queries/graphql_query/permissions'
with open(self.dir + '/user_select_query_unpublished_articles.yaml') as c:
self.conf = yaml.safe_load(c)
curr_time = datetime.now()
curr_time = datetime.utcnow()
exp_time = curr_time + timedelta(hours=1)
self.claims = {
'sub': '1234567890',

View File

@ -0,0 +1,84 @@
from datetime import datetime, timedelta
import math
import json
import time
import base64
import ruamel.yaml as yaml
import pytest
from test_subscriptions import init_ws_conn
from context import PytestConf
if not PytestConf.config.getoption('--hge-webhook'):
pytest.skip('--hge-webhook is missing, skipping webhook expiration tests', allow_module_level=True)
usefixtures = pytest.mark.usefixtures
@pytest.fixture(scope='function')
def ws_conn_recreate(ws_client):
ws_client.recreate_conn()
def connect_with(hge_ctx, ws_client, headers):
headers['X-Hasura-Role'] = 'user'
headers['X-Hasura-User-Id'] = '1234321'
headers['X-Hasura-Auth-Mode'] = 'webhook'
token = base64.b64encode(json.dumps(headers).encode('utf-8')).decode('utf-8')
headers['Authorization'] = 'Bearer ' + token
payload = {'headers': headers}
init_ws_conn(hge_ctx, ws_client, payload)
EXPIRE_TIME_FORMAT = '%a, %d %b %Y %T GMT'
@usefixtures('ws_conn_recreate')
class TestWebhookSubscriptionExpiry(object):
def test_expiry_with_no_header(self, hge_ctx, ws_client):
# no expiry time => the connextion will remain alive
connect_with(hge_ctx, ws_client, {})
time.sleep(5)
assert ws_client.remote_closed == False, ws_client.remote_closed
def test_expiry_with_expires_header(self, hge_ctx, ws_client):
exp = datetime.utcnow() + timedelta(seconds=6)
connect_with(hge_ctx, ws_client, {
'Expires': exp.strftime(EXPIRE_TIME_FORMAT)
})
time.sleep(4)
assert ws_client.remote_closed == False, ws_client.remote_closed
time.sleep(4)
assert ws_client.remote_closed == True, ws_client.remote_closed
def test_expiry_with_cache_control(self, hge_ctx, ws_client):
connect_with(hge_ctx, ws_client, {
'Cache-Control': 'max-age=6'
})
time.sleep(4)
assert ws_client.remote_closed == False, ws_client.remote_closed
time.sleep(4)
assert ws_client.remote_closed == True, ws_client.remote_closed
def test_expiry_with_both(self, hge_ctx, ws_client):
exp = datetime.utcnow() + timedelta(seconds=6)
connect_with(hge_ctx, ws_client, {
'Expires': exp.strftime(EXPIRE_TIME_FORMAT),
'Cache-Control': 'max-age=10',
})
# cache-control has precedence, so the expiry time will be five seconds
time.sleep(4)
assert ws_client.remote_closed == False, ws_client.remote_closed
time.sleep(4)
assert ws_client.remote_closed == False, ws_client.remote_closed
time.sleep(4)
assert ws_client.remote_closed == True, ws_client.remote_closed
def test_expiry_with_parse_error(self, hge_ctx, ws_client):
exp = datetime.utcnow() + timedelta(seconds=3)
connect_with(hge_ctx, ws_client, {
'Expires': exp.strftime('%a, %d %m %Y %T UTC'),
'Cache-Control': 'maxage=3',
})
# neither will parse, the connection will remain alive
time.sleep(5)
assert ws_client.remote_closed == False, ws_client.remote_closed