mirror of
https://github.com/hasura/graphql-engine.git
synced 2024-12-15 09:22:43 +03:00
This commit is contained in:
parent
b47b629c93
commit
10d8529d28
@ -45,6 +45,8 @@ For ``serve`` subcommand these are the flags available
|
||||
verifying. e.g: `{"type": "HS256", "key":
|
||||
"<your-hmac-shared-secret>"}`,`{"type": "RS256",
|
||||
"key": "<your-PEM-RSA-public-key>"}
|
||||
--unauthorized-role Unauthorized role, used when access-key is not sent in access-key
|
||||
only mode or "Authorization" header is absent in JWT mode
|
||||
-s, --stripes Number of stripes
|
||||
-c, --connections Number of connections that need to be opened to Postgres
|
||||
--timeout Each connection's idle time before it is closed
|
||||
@ -60,11 +62,14 @@ Default environment variables
|
||||
|
||||
You can use environment variables to configure defaults instead of using flags:
|
||||
|
||||
.. note::
|
||||
When the equivalent flags for environment variables are used, the flags will take precedence.
|
||||
|
||||
For example:
|
||||
|
||||
.. code-block:: bash
|
||||
|
||||
HASURA_GRAPHQL_DATABASE_URL=postgres://user:pass@host:5432/dbname graphql-engine serve
|
||||
$ HASURA_GRAPHQL_DATABASE_URL=postgres://user:pass@host:5432/dbname graphql-engine serve
|
||||
|
||||
|
||||
These are the environment variables which are available:
|
||||
@ -91,8 +96,6 @@ These are the environment variables which are available:
|
||||
"key": "<your-PEM-RSA-public-key>"}
|
||||
Enable JWT mode, the value of which is a JSON
|
||||
|
||||
HASURA_GRAPHQL_UNAUTHORIZED_ROLE Unauthorized role, used when access-key is not sent in access-key
|
||||
only mode or "Authorization" header is absent in JWT mode
|
||||
HASURA_GRAPHQL_ENABLE_CONSOLE Enable API console. It is served at '/' and '/console'
|
||||
|
||||
|
||||
.. note::
|
||||
When the equivalent flags for environment variables are used, the flags will take precedence.
|
||||
|
@ -7,7 +7,6 @@ module Main where
|
||||
import Ops
|
||||
|
||||
import Control.Monad.STM (atomically)
|
||||
import Data.IORef (newIORef)
|
||||
import Data.Time.Clock (getCurrentTime)
|
||||
import Options.Applicative
|
||||
import System.Environment (lookupEnv)
|
||||
@ -18,7 +17,6 @@ import qualified Data.Aeson as A
|
||||
import qualified Data.ByteString.Char8 as BC
|
||||
import qualified Data.ByteString.Lazy as BL
|
||||
import qualified Data.ByteString.Lazy.Char8 as BLC
|
||||
import qualified Data.String.Conversions as CS
|
||||
import qualified Data.Text as T
|
||||
import qualified Data.Yaml as Y
|
||||
import qualified Network.HTTP.Client as HTTP
|
||||
@ -26,10 +24,10 @@ import qualified Network.HTTP.Client.TLS as HTTP
|
||||
import qualified Network.Wai.Handler.Warp as Warp
|
||||
|
||||
import Hasura.Events.Lib
|
||||
import Hasura.Logging (LoggerCtx, defaultLoggerSettings,
|
||||
mkLogger, mkLoggerCtx)
|
||||
import Hasura.Logging (defaultLoggerSettings, mkLoggerCtx)
|
||||
import Hasura.Prelude
|
||||
import Hasura.RQL.DDL.Metadata (fetchMetadata)
|
||||
import Hasura.RQL.Types (RoleName (..))
|
||||
import Hasura.Server.App (mkWaiApp)
|
||||
import Hasura.Server.Auth
|
||||
import Hasura.Server.CheckUpdates (checkForUpdates)
|
||||
@ -54,6 +52,7 @@ data ServeOptions
|
||||
, soAccessKey :: !(Maybe AccessKey)
|
||||
, soWebHook :: !(Maybe Webhook)
|
||||
, soJwtSecret :: !(Maybe Text)
|
||||
, soUnAuthRole :: !(Maybe RoleName)
|
||||
, soCorsConfig :: !CorsConfigFlags
|
||||
, soEnableConsole :: !Bool
|
||||
} deriving (Show, Eq)
|
||||
@ -86,6 +85,7 @@ parseRavenMode = subparser
|
||||
<*> parseAccessKey
|
||||
<*> parseWebHook
|
||||
<*> parseJwtSecret
|
||||
<*> parseUnAuthRole
|
||||
<*> parseCorsConfig
|
||||
<*> parseEnableConsole
|
||||
|
||||
@ -103,61 +103,6 @@ printJSON = BLC.putStrLn . A.encode
|
||||
printYaml :: (A.ToJSON a) => a -> IO ()
|
||||
printYaml = BC.putStrLn . Y.encode
|
||||
|
||||
mkAuthMode
|
||||
:: ( MonadIO m
|
||||
, MonadError T.Text m
|
||||
)
|
||||
=> Maybe AccessKey
|
||||
-> Maybe Webhook
|
||||
-> Maybe T.Text
|
||||
-> HTTP.Manager
|
||||
-> LoggerCtx
|
||||
-> m AuthMode
|
||||
mkAuthMode mAccessKey mWebHook mJwtSecret httpManager lCtx =
|
||||
case (mAccessKey, mWebHook, mJwtSecret) of
|
||||
(Nothing, Nothing, Nothing) -> return AMNoAuth
|
||||
(Just key, Nothing, Nothing) -> return $ AMAccessKey key
|
||||
(Just key, Just hook, Nothing) -> return $ AMAccessKeyAndHook key hook
|
||||
(Just key, Nothing, Just jwtConf) ->
|
||||
AMAccessKeyAndJWT key <$> mkJwtCtx jwtConf httpManager lCtx
|
||||
|
||||
(Nothing, Just _, Nothing) -> throwError $
|
||||
"Fatal Error : --auth-hook (HASURA_GRAPHQL_AUTH_HOOK)"
|
||||
<> " requires --access-key (HASURA_GRAPHQL_ACCESS_KEY) to be set"
|
||||
(Nothing, Nothing, Just _) -> throwError $
|
||||
"Fatal Error : --jwt-secret (HASURA_GRAPHQL_JWT_SECRET)"
|
||||
<> " requires --access-key (HASURA_GRAPHQL_ACCESS_KEY) to be set"
|
||||
(Nothing, Just _, Just _) -> throwError
|
||||
"Fatal Error: Both webhook and JWT mode cannot be enabled at the same time"
|
||||
(Just _, Just _, Just _) -> throwError
|
||||
"Fatal Error: Both webhook and JWT mode cannot be enabled at the same time"
|
||||
|
||||
mkJwtCtx
|
||||
:: ( MonadIO m
|
||||
, MonadError T.Text m
|
||||
)
|
||||
=> T.Text
|
||||
-> HTTP.Manager
|
||||
-> LoggerCtx
|
||||
-> m JWTCtx
|
||||
mkJwtCtx jwtConf httpManager loggerCtx = do
|
||||
-- the JWT Conf as JSON string; try to parse it
|
||||
conf <- either decodeErr return $ A.eitherDecodeStrict $ CS.cs jwtConf
|
||||
jwkRef <- case jcKeyOrUrl conf of
|
||||
Left jwk -> liftIO $ newIORef (JWKSet [jwk])
|
||||
Right url -> do
|
||||
ref <- liftIO $ newIORef $ JWKSet []
|
||||
let logger = mkLogger loggerCtx
|
||||
mTime <- updateJwkRef logger httpManager url ref
|
||||
case mTime of
|
||||
Nothing -> return ref
|
||||
Just t -> do
|
||||
jwkRefreshCtrl logger httpManager url ref t
|
||||
return ref
|
||||
return $ JWTCtx jwkRef (jcClaimNs conf) (jcAudience conf)
|
||||
where
|
||||
decodeErr e = throwError . T.pack $ "Fatal Error: JWT conf: " <> e
|
||||
|
||||
getEnableConsoleEnv :: IO Bool
|
||||
getEnableConsoleEnv = do
|
||||
mVal <- fmap T.pack <$> lookupEnv enableConsoleEnvVar
|
||||
@ -189,16 +134,18 @@ main = do
|
||||
httpManager <- HTTP.newManager HTTP.tlsManagerSettings
|
||||
case ravenMode of
|
||||
ROServe (ServeOptions port cp isoL mRootDir mAccessKey mWebHook mJwtSecret
|
||||
corsCfg enableConsole) -> do
|
||||
mUnAuthRole corsCfg enableConsole) -> do
|
||||
|
||||
-- get all auth mode related config
|
||||
mFinalAccessKey <- considerEnv "HASURA_GRAPHQL_ACCESS_KEY" $ getAccessKey <$> mAccessKey
|
||||
mFinalWebHook <- considerEnv "HASURA_GRAPHQL_AUTH_HOOK" $ getWebhook <$> mWebHook
|
||||
mFinalJwtSecret <- considerEnv "HASURA_GRAPHQL_JWT_SECRET" mJwtSecret
|
||||
mFinalUnAuthRole <- considerEnv "HASURA_GRAPHQL_UNAUTHORIZED_ROLE" $ getRoleTxt <$> mUnAuthRole
|
||||
-- prepare auth mode
|
||||
authModeRes <- runExceptT $ mkAuthMode (AccessKey <$> mFinalAccessKey)
|
||||
(Webhook <$> mFinalWebHook)
|
||||
mFinalJwtSecret
|
||||
(RoleName <$> mFinalUnAuthRole)
|
||||
httpManager
|
||||
loggerCtx
|
||||
am <- either ((>> exitFailure) . putStrLn . T.unpack) return authModeRes
|
||||
|
@ -9,6 +9,7 @@
|
||||
module Hasura.Server.Auth
|
||||
( getUserInfo
|
||||
, AuthMode(..)
|
||||
, mkAuthMode
|
||||
, AccessKey (..)
|
||||
, Webhook (..)
|
||||
-- JWT related
|
||||
@ -21,25 +22,28 @@ module Hasura.Server.Auth
|
||||
, jwkRefreshCtrl
|
||||
) where
|
||||
|
||||
import Control.Exception (try)
|
||||
import Control.Exception (try)
|
||||
import Control.Lens
|
||||
import Data.Aeson
|
||||
import Data.CaseInsensitive (CI (..), original)
|
||||
import Data.CaseInsensitive (CI (..), original)
|
||||
import Data.IORef (newIORef)
|
||||
|
||||
import qualified Data.ByteString.Lazy as BL
|
||||
import qualified Data.HashMap.Strict as M
|
||||
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 qualified Data.ByteString.Lazy as BL
|
||||
import qualified Data.HashMap.Strict as M
|
||||
import qualified Data.String.Conversions as CS
|
||||
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.Logging
|
||||
import Hasura.Prelude
|
||||
import Hasura.RQL.Types
|
||||
import Hasura.Server.Auth.JWT
|
||||
import Hasura.Server.Logging
|
||||
import Hasura.Server.Utils
|
||||
|
||||
import qualified Hasura.Logging as L
|
||||
import qualified Hasura.Logging as L
|
||||
|
||||
|
||||
newtype AccessKey
|
||||
@ -52,11 +56,73 @@ newtype Webhook
|
||||
|
||||
data AuthMode
|
||||
= AMNoAuth
|
||||
| AMAccessKey !AccessKey
|
||||
| AMAccessKey !AccessKey !(Maybe RoleName)
|
||||
| AMAccessKeyAndHook !AccessKey !Webhook
|
||||
| AMAccessKeyAndJWT !AccessKey !JWTCtx
|
||||
| AMAccessKeyAndJWT !AccessKey !JWTCtx !(Maybe RoleName)
|
||||
deriving (Show, Eq)
|
||||
|
||||
mkAuthMode
|
||||
:: ( MonadIO m
|
||||
, MonadError T.Text m
|
||||
)
|
||||
=> Maybe AccessKey
|
||||
-> Maybe Webhook
|
||||
-> Maybe T.Text
|
||||
-> Maybe RoleName
|
||||
-> H.Manager
|
||||
-> LoggerCtx
|
||||
-> m AuthMode
|
||||
mkAuthMode mAccessKey mWebHook mJwtSecret mUnAuthRole httpManager lCtx =
|
||||
case (mAccessKey, mWebHook, mJwtSecret) of
|
||||
(Nothing, Nothing, Nothing) -> return AMNoAuth
|
||||
(Just key, Nothing, Nothing) -> return $ AMAccessKey key mUnAuthRole
|
||||
(Just key, Just hook, Nothing) -> unAuthRoleNotReqForWebHook >>
|
||||
return (AMAccessKeyAndHook key hook)
|
||||
(Just key, Nothing, Just jwtConf) -> do
|
||||
jwtCtx <- mkJwtCtx jwtConf httpManager lCtx
|
||||
return $ AMAccessKeyAndJWT key jwtCtx mUnAuthRole
|
||||
|
||||
(Nothing, Just _, Nothing) -> throwError $
|
||||
"Fatal Error : --auth-hook (HASURA_GRAPHQL_AUTH_HOOK)"
|
||||
<> " requires --access-key (HASURA_GRAPHQL_ACCESS_KEY) to be set"
|
||||
(Nothing, Nothing, Just _) -> throwError $
|
||||
"Fatal Error : --jwt-secret (HASURA_GRAPHQL_JWT_SECRET)"
|
||||
<> " requires --access-key (HASURA_GRAPHQL_ACCESS_KEY) to be set"
|
||||
(Nothing, Just _, Just _) -> throwError
|
||||
"Fatal Error: Both webhook and JWT mode cannot be enabled at the same time"
|
||||
(Just _, Just _, Just _) -> throwError
|
||||
"Fatal Error: Both webhook and JWT mode cannot be enabled at the same time"
|
||||
where
|
||||
unAuthRoleNotReqForWebHook =
|
||||
when (isJust mUnAuthRole) $
|
||||
throwError $ "Fatal Error: --unauthorized-role (HASURA_GRAPHQL_UNAUTHORIZED_ROLE) is not allowed"
|
||||
<> " when --auth-hook (HASURA_GRAPHQL_AUTH_HOOK) is set"
|
||||
|
||||
mkJwtCtx
|
||||
:: ( MonadIO m
|
||||
, MonadError T.Text m
|
||||
)
|
||||
=> T.Text
|
||||
-> H.Manager
|
||||
-> LoggerCtx
|
||||
-> m JWTCtx
|
||||
mkJwtCtx jwtConf httpManager loggerCtx = do
|
||||
-- the JWT Conf as JSON string; try to parse it
|
||||
conf <- either decodeErr return $ eitherDecodeStrict $ CS.cs jwtConf
|
||||
jwkRef <- case jcKeyOrUrl conf of
|
||||
Left jwk -> liftIO $ newIORef (JWKSet [jwk])
|
||||
Right url -> do
|
||||
ref <- liftIO $ newIORef $ JWKSet []
|
||||
let logger = mkLogger loggerCtx
|
||||
mTime <- updateJwkRef logger httpManager url ref
|
||||
case mTime of
|
||||
Nothing -> return ref
|
||||
Just t -> do
|
||||
jwkRefreshCtrl logger httpManager url ref t
|
||||
return ref
|
||||
return $ JWTCtx jwkRef (jcClaimNs conf) (jcAudience conf)
|
||||
where
|
||||
decodeErr e = throwError . T.pack $ "Fatal Error: JWT conf: " <> e
|
||||
|
||||
mkUserInfoFromResp
|
||||
:: (MonadIO m, MonadError QErr m)
|
||||
@ -145,16 +211,16 @@ getUserInfo logger manager rawHeaders = \case
|
||||
|
||||
AMNoAuth -> return userInfoFromHeaders
|
||||
|
||||
AMAccessKey accKey ->
|
||||
AMAccessKey accKey unAuthRole ->
|
||||
case getHeader accessKeyHeader of
|
||||
Just givenAccKey -> userInfoWhenAccessKey accKey givenAccKey
|
||||
Nothing -> throw401 $ accessKeyHeader <> " required, but not found"
|
||||
Nothing -> userInfoWhenNoAccessKey unAuthRole
|
||||
|
||||
AMAccessKeyAndHook accKey hook ->
|
||||
whenAccessKeyAbsent accKey (userInfoFromWebhook logger manager hook rawHeaders)
|
||||
|
||||
AMAccessKeyAndJWT accKey jwtSecret ->
|
||||
whenAccessKeyAbsent accKey (processJwt jwtSecret rawHeaders)
|
||||
AMAccessKeyAndJWT accKey jwtSecret unAuthRole ->
|
||||
whenAccessKeyAbsent accKey (processJwt jwtSecret rawHeaders unAuthRole)
|
||||
|
||||
where
|
||||
-- when access key is absent, run the action to retrieve UserInfo, otherwise
|
||||
@ -178,3 +244,8 @@ getUserInfo logger manager rawHeaders = \case
|
||||
userInfoWhenAccessKey key reqKey = do
|
||||
when (reqKey /= getAccessKey key) $ throw401 $ "invalid " <> accessKeyHeader
|
||||
return userInfoFromHeaders
|
||||
|
||||
userInfoWhenNoAccessKey = \case
|
||||
Nothing -> throw401 $ accessKeyHeader <> " required, but not found"
|
||||
Just role -> return $ UserInfo role $
|
||||
M.insertWith const userRoleHeader (getRoleTxt role) headers
|
||||
|
@ -14,6 +14,7 @@ module Hasura.Server.Auth.JWT
|
||||
, jwkRefreshCtrl
|
||||
) where
|
||||
|
||||
import Control.Arrow (first)
|
||||
import Control.Exception (try)
|
||||
import Control.Lens
|
||||
import Control.Monad (when)
|
||||
@ -164,8 +165,31 @@ processJwt
|
||||
, MonadError QErr m)
|
||||
=> JWTCtx
|
||||
-> HTTP.RequestHeaders
|
||||
-> Maybe RoleName
|
||||
-> m UserInfo
|
||||
processJwt jwtCtx headers = do
|
||||
processJwt jwtCtx headers mUnAuthRole =
|
||||
maybe withoutAuthZHeader withAuthZHeader mAuthZHeader
|
||||
where
|
||||
mAuthZHeader = find (\h -> fst h == CI.mk "Authorization") headers
|
||||
|
||||
withAuthZHeader (_, authzHeader) =
|
||||
processAuthZHeader jwtCtx headers $ BL.fromStrict authzHeader
|
||||
|
||||
withoutAuthZHeader = do
|
||||
unAuthRole <- maybe missingAuthzHeader return mUnAuthRole
|
||||
return $ UserInfo unAuthRole
|
||||
$ Map.singleton userRoleHeader $ getRoleTxt unAuthRole
|
||||
missingAuthzHeader =
|
||||
throw400 InvalidHeaders "Missing Authorization header in JWT authentication mode"
|
||||
|
||||
processAuthZHeader
|
||||
:: ( MonadIO m
|
||||
, MonadError QErr m)
|
||||
=> JWTCtx
|
||||
-> HTTP.RequestHeaders
|
||||
-> BLC.ByteString
|
||||
-> m UserInfo
|
||||
processAuthZHeader jwtCtx headers authzHeader = do
|
||||
-- try to parse JWT token from Authorization header
|
||||
jwt <- parseAuthzHeader
|
||||
|
||||
@ -182,7 +206,7 @@ processJwt jwtCtx headers = do
|
||||
|
||||
-- filter only x-hasura claims and convert to lower-case
|
||||
let claimsMap = Map.filterWithKey (\k _ -> T.isPrefixOf "x-hasura-" k)
|
||||
$ Map.fromList $ map (\(k, v) -> (T.toLower k, v))
|
||||
$ Map.fromList $ map (first T.toLower)
|
||||
$ Map.toList hasuraClaims
|
||||
|
||||
HasuraClaims allowedRoles defaultRole <- parseHasuraClaims claimsMap
|
||||
@ -203,9 +227,7 @@ processJwt jwtCtx headers = do
|
||||
|
||||
where
|
||||
parseAuthzHeader = do
|
||||
let mAuthzHeader = find (\h -> fst h == CI.mk "Authorization") headers
|
||||
(_, authzHeader) <- maybe missingAuthzHeader return mAuthzHeader
|
||||
let tokenParts = BLC.words $ BL.fromStrict authzHeader
|
||||
let tokenParts = BLC.words authzHeader
|
||||
case tokenParts of
|
||||
["Bearer", jwt] -> return jwt
|
||||
_ -> malformedAuthzHeader
|
||||
@ -235,8 +257,6 @@ processJwt jwtCtx headers = do
|
||||
|
||||
malformedAuthzHeader =
|
||||
throw400 InvalidHeaders "Malformed Authorization header"
|
||||
missingAuthzHeader =
|
||||
throw400 InvalidHeaders "Missing Authorization header in JWT authentication mode"
|
||||
currRoleNotAllowed =
|
||||
throw400 AccessDenied "Your current role is not in allowed roles"
|
||||
claimsNotFound = do
|
||||
|
@ -12,6 +12,7 @@ import qualified Data.Text as T
|
||||
|
||||
import Hasura.Prelude
|
||||
import Hasura.RQL.DDL.Utils
|
||||
import Hasura.RQL.Types (RoleName (..))
|
||||
import Hasura.Server.Auth
|
||||
import Hasura.Server.Utils
|
||||
|
||||
@ -184,6 +185,15 @@ jwtSecretHelp = "The JSON containing type and the JWK used for verifying. e.g: "
|
||||
<> "`{\"type\": \"HS256\", \"key\": \"<your-hmac-shared-secret>\", \"claims_namespace\": \"<optional-custom-claims-key-name>\"}`,"
|
||||
<> "`{\"type\": \"RS256\", \"key\": \"<your-PEM-RSA-public-key>\", \"claims_namespace\": \"<optional-custom-claims-key-name>\"}`"
|
||||
|
||||
parseUnAuthRole :: Parser (Maybe RoleName)
|
||||
parseUnAuthRole =
|
||||
optional $ RoleName <$>
|
||||
strOption ( long "unauthorized-role" <>
|
||||
metavar "UNAUTHORIZED ROLE" <>
|
||||
help ( "Unauthorized role, used when access-key is not sent in access-key only mode "
|
||||
++ "or \"Authorization\" header is absent in JWT mode"
|
||||
)
|
||||
)
|
||||
|
||||
parseCorsConfig :: Parser CorsConfigFlags
|
||||
parseCorsConfig =
|
||||
|
Loading…
Reference in New Issue
Block a user