graphql-engine/server/src-lib/Hasura/Server/Auth.hs

255 lines
9.9 KiB
Haskell
Raw Normal View History

{-# LANGUAGE DerivingStrategies #-}
module Hasura.Server.Auth
[Preview] Inherited roles for postgres read queries fixes #3868 docker image - `hasura/graphql-engine:inherited-roles-preview-48b73a2de` Note: To be able to use the inherited roles feature, the graphql-engine should be started with the env variable `HASURA_GRAPHQL_EXPERIMENTAL_FEATURES` set to `inherited_roles`. Introduction ------------ This PR implements the idea of multiple roles as presented in this [paper](https://www.microsoft.com/en-us/research/wp-content/uploads/2016/02/FGALanguageICDE07.pdf). The multiple roles feature in this PR can be used via inherited roles. An inherited role is a role which can be created by combining multiple singular roles. For example, if there are two roles `author` and `editor` configured in the graphql-engine, then we can create a inherited role with the name of `combined_author_editor` role which will combine the select permissions of the `author` and `editor` roles and then make GraphQL queries using the `combined_author_editor`. How are select permissions of different roles are combined? ------------------------------------------------------------ A select permission includes 5 things: 1. Columns accessible to the role 2. Row selection filter 3. Limit 4. Allow aggregation 5. Scalar computed fields accessible to the role Suppose there are two roles, `role1` gives access to the `address` column with row filter `P1` and `role2` gives access to both the `address` and the `phone` column with row filter `P2` and we create a new role `combined_roles` which combines `role1` and `role2`. Let's say the following GraphQL query is queried with the `combined_roles` role. ```graphql query { employees { address phone } } ``` This will translate to the following SQL query: ```sql select (case when (P1 or P2) then address else null end) as address, (case when P2 then phone else null end) as phone from employee where (P1 or P2) ``` The other parameters of the select permission will be combined in the following manner: 1. Limit - Minimum of the limits will be the limit of the inherited role 2. Allow aggregations - If any of the role allows aggregation, then the inherited role will allow aggregation 3. Scalar computed fields - same as table column fields, as in the above example APIs for inherited roles: ---------------------- 1. `add_inherited_role` `add_inherited_role` is the [metadata API](https://hasura.io/docs/1.0/graphql/core/api-reference/index.html#schema-metadata-api) to create a new inherited role. It accepts two arguments `role_name`: the name of the inherited role to be added (String) `role_set`: list of roles that need to be combined (Array of Strings) Example: ```json { "type": "add_inherited_role", "args": { "role_name":"combined_user", "role_set":[ "user", "user1" ] } } ``` After adding the inherited role, the inherited role can be used like single roles like earlier Note: An inherited role can only be created with non-inherited/singular roles. 2. `drop_inherited_role` The `drop_inherited_role` API accepts the name of the inherited role and drops it from the metadata. It accepts a single argument: `role_name`: name of the inherited role to be dropped Example: ```json { "type": "drop_inherited_role", "args": { "role_name":"combined_user" } } ``` Metadata --------- The derived roles metadata will be included under the `experimental_features` key while exporting the metadata. ```json { "experimental_features": { "derived_roles": [ { "role_name": "manager_is_employee_too", "role_set": [ "employee", "manager" ] } ] } } ``` Scope ------ Only postgres queries and subscriptions are supported in this PR. Important points: ----------------- 1. All columns exposed to an inherited role will be marked as `nullable`, this is done so that cell value nullification can be done. TODOs ------- - [ ] Tests - [ ] Test a GraphQL query running with a inherited role without enabling inherited roles in experimental features - [] Tests for aggregate queries, limit, computed fields, functions, subscriptions (?) - [ ] Introspection test with a inherited role (nullability changes in a inherited role) - [ ] Docs - [ ] Changelog Co-authored-by: Vamshi Surabhi <6562944+0x777@users.noreply.github.com> GitOrigin-RevId: 3b8ee1e11f5ceca80fe294f8c074d42fbccfec63
2021-03-08 14:14:13 +03:00
( getUserInfoWithExpTime
, AuthMode (..)
, setupAuthMode
, AdminSecretHash
, hashAdminSecret
-- * WebHook related
, AuthHookType (..)
, AuthHookG (..)
, AuthHook
-- * JWT related
add support for jwt authorization (close #186) (#255) The API: 1. HGE has `--jwt-secret` flag or `HASURA_GRAPHQL_JWT_SECRET` env var. The value of which is a JSON. 2. The structure of this JSON is: `{"type": "<standard-JWT-algorithms>", "key": "<the-key>"}` `type` : Standard JWT algos : `HS256`, `RS256`, `RS512` etc. (see jwt.io). `key`: i. Incase of symmetric key, the key as it is. ii. Incase of asymmetric keys, only the public key, in a PEM encoded string or as a X509 certificate. 3. The claims in the JWT token must contain the following: i. `x-hasura-default-role` field: default role of that user ii. `x-hasura-allowed-roles` : A list of allowed roles for the user. The default role is overriden by `x-hasura-role` header. 4. The claims in the JWT token, can have other `x-hasura-*` fields where their values can only be strings. 5. The JWT tokens are sent as `Authorization: Bearer <token>` headers. --- To test: 1. Generate a shared secret (for HMAC-SHA256) or RSA key pair. 2. Goto https://jwt.io/ , add the keys 3. Edit the claims to have `x-hasura-role` (mandatory) and other `x-hasura-*` fields. Add permissions related to the claims to test permissions. 4. Start HGE with `--jwt-secret` flag or `HASURA_GRAPHQL_JWT_SECRET` env var, which takes a JSON string: `{"type": "HS256", "key": "mylongsharedsecret"}` or `{"type":"RS256", "key": "<PEM-encoded-public-key>"}` 5. Copy the JWT token from jwt.io and use it in the `Authorization: Bearer <token>` header. --- TODO: Support EC public keys. It is blocked on frasertweedale/hs-jose#61
2018-08-30 13:32:09 +03:00
, RawJWT
, JWTConfig (..)
, JWTCtx (..)
, JWKSet (..)
add support for jwt authorization (close #186) (#255) The API: 1. HGE has `--jwt-secret` flag or `HASURA_GRAPHQL_JWT_SECRET` env var. The value of which is a JSON. 2. The structure of this JSON is: `{"type": "<standard-JWT-algorithms>", "key": "<the-key>"}` `type` : Standard JWT algos : `HS256`, `RS256`, `RS512` etc. (see jwt.io). `key`: i. Incase of symmetric key, the key as it is. ii. Incase of asymmetric keys, only the public key, in a PEM encoded string or as a X509 certificate. 3. The claims in the JWT token must contain the following: i. `x-hasura-default-role` field: default role of that user ii. `x-hasura-allowed-roles` : A list of allowed roles for the user. The default role is overriden by `x-hasura-role` header. 4. The claims in the JWT token, can have other `x-hasura-*` fields where their values can only be strings. 5. The JWT tokens are sent as `Authorization: Bearer <token>` headers. --- To test: 1. Generate a shared secret (for HMAC-SHA256) or RSA key pair. 2. Goto https://jwt.io/ , add the keys 3. Edit the claims to have `x-hasura-role` (mandatory) and other `x-hasura-*` fields. Add permissions related to the claims to test permissions. 4. Start HGE with `--jwt-secret` flag or `HASURA_GRAPHQL_JWT_SECRET` env var, which takes a JSON string: `{"type": "HS256", "key": "mylongsharedsecret"}` or `{"type":"RS256", "key": "<PEM-encoded-public-key>"}` 5. Copy the JWT token from jwt.io and use it in the `Authorization: Bearer <token>` header. --- TODO: Support EC public keys. It is blocked on frasertweedale/hs-jose#61
2018-08-30 13:32:09 +03:00
, processJwt
, updateJwkRef
, UserAuthentication (..)
-- * Exposed for testing
, getUserInfoWithExpTime_
) where
import Hasura.Prelude
import qualified Crypto.Hash as Crypto
import qualified Data.Text.Encoding as T
import qualified Network.HTTP.Client as H
import qualified Network.HTTP.Types as N
import Control.Concurrent.Extended (ForkableMonadIO, forkManagedT)
import Control.Monad.Morph (hoist)
import Control.Monad.Trans.Control (MonadBaseControl)
import Control.Monad.Trans.Managed (ManagedT)
import Data.IORef (newIORef)
import Data.Time.Clock (UTCTime)
import qualified Hasura.Tracing as Tracing
import Hasura.Logging
import Hasura.RQL.Types
import Hasura.Server.Auth.JWT hiding (processJwt_)
import Hasura.Server.Auth.WebHook
add support for jwt authorization (close #186) (#255) The API: 1. HGE has `--jwt-secret` flag or `HASURA_GRAPHQL_JWT_SECRET` env var. The value of which is a JSON. 2. The structure of this JSON is: `{"type": "<standard-JWT-algorithms>", "key": "<the-key>"}` `type` : Standard JWT algos : `HS256`, `RS256`, `RS512` etc. (see jwt.io). `key`: i. Incase of symmetric key, the key as it is. ii. Incase of asymmetric keys, only the public key, in a PEM encoded string or as a X509 certificate. 3. The claims in the JWT token must contain the following: i. `x-hasura-default-role` field: default role of that user ii. `x-hasura-allowed-roles` : A list of allowed roles for the user. The default role is overriden by `x-hasura-role` header. 4. The claims in the JWT token, can have other `x-hasura-*` fields where their values can only be strings. 5. The JWT tokens are sent as `Authorization: Bearer <token>` headers. --- To test: 1. Generate a shared secret (for HMAC-SHA256) or RSA key pair. 2. Goto https://jwt.io/ , add the keys 3. Edit the claims to have `x-hasura-role` (mandatory) and other `x-hasura-*` fields. Add permissions related to the claims to test permissions. 4. Start HGE with `--jwt-secret` flag or `HASURA_GRAPHQL_JWT_SECRET` env var, which takes a JSON string: `{"type": "HS256", "key": "mylongsharedsecret"}` or `{"type":"RS256", "key": "<PEM-encoded-public-key>"}` 5. Copy the JWT token from jwt.io and use it in the `Authorization: Bearer <token>` header. --- TODO: Support EC public keys. It is blocked on frasertweedale/hs-jose#61
2018-08-30 13:32:09 +03:00
import Hasura.Server.Utils
import Hasura.Server.Version (HasVersion)
backend only insert permissions (rfc #4120) (#4224) * move user info related code to Hasura.User module * the RFC #4120 implementation; insert permissions with admin secret * revert back to old RoleName based schema maps An attempt made to avoid duplication of schema contexts in types if any role doesn't possess any admin secret specific schema * fix compile errors in haskell test * keep 'user_vars' for session variables in http-logs * no-op refacto * tests for admin only inserts * update docs for admin only inserts * updated CHANGELOG.md * default behaviour when admin secret is not set * fix x-hasura-role to X-Hasura-Role in pytests * introduce effective timeout in actions async tests * update docs for admin-secret not configured case * Update docs/graphql/manual/api-reference/schema-metadata-api/permission.rst Co-Authored-By: Marion Schleifer <marion@hasura.io> * Apply suggestions from code review Co-Authored-By: Marion Schleifer <marion@hasura.io> * a complete iteration backend insert permissions accessable via 'x-hasura-backend-privilege' session variable * console changes for backend-only permissions * provide tooltip id; update labels and tooltips; * requested changes * requested changes - remove className from Toggle component - use appropriate function name (capitalizeFirstChar -> capitalize) * use toggle props from definitelyTyped * fix accidental commit * Revert "introduce effective timeout in actions async tests" This reverts commit b7a59c19d643520cfde6af579889e1038038438a. * generate complete schema for both 'default' and 'backend' sessions * Apply suggestions from code review Co-Authored-By: Marion Schleifer <marion@hasura.io> * remove unnecessary import, export Toggle as is * update session variable in tooltip * 'x-hasura-use-backend-only-permissions' variable to switch * update help texts * update docs * update docs * update console help text * regenerate package-lock * serve no backend schema when backend_only: false and header set to true - Few type name refactor as suggested by @0x777 * update CHANGELOG.md * Update CHANGELOG.md * Update CHANGELOG.md * fix a merge bug where a certain entity didn't get removed Co-authored-by: Marion Schleifer <marion@hasura.io> Co-authored-by: Rishichandra Wawhal <rishi@hasura.io> Co-authored-by: rikinsk <rikin.kachhia@gmail.com> Co-authored-by: Tirumarai Selvan <tiru@hasura.io>
2020-04-24 12:10:53 +03:00
import Hasura.Session
-- | Typeclass representing the @UserInfo@ authorization and resolving effect
class (Monad m) => UserAuthentication m where
resolveUserInfo
:: HasVersion
=> Logger Hasura
-> H.Manager
-> [N.Header]
-- ^ request headers
-> AuthMode
-> Maybe ReqsText
-> m (Either QErr (UserInfo, Maybe UTCTime))
-- | The hashed admin password. 'hashAdminSecret' is our public interface for
-- constructing the secret.
--
-- To prevent misuse and leaking we keep this opaque and don't provide
-- instances that could leak information. Likewise for 'AuthMode'.
--
-- Although this exists only in memory we store only a hash of the admin secret
-- primarily in order to:
--
-- - prevent theoretical timing attacks from a naive `==` check
-- - prevent misuse or inadvertent leaking of the secret
--
newtype AdminSecretHash = AdminSecretHash (Crypto.Digest Crypto.SHA512)
deriving (Ord, Eq)
-- We don't want to be able to leak the secret hash. This is a dummy instance
-- to support 'Show AuthMode' which we want for testing.
instance Show AdminSecretHash where
show _ = "(error \"AdminSecretHash hidden\")"
hashAdminSecret :: Text -> AdminSecretHash
hashAdminSecret = AdminSecretHash . Crypto.hash . T.encodeUtf8
-- | The methods we'll use to derive roles for authenticating requests.
--
-- @Maybe RoleName@ below is the optionally-defined role for the
-- unauthenticated (anonymous) user.
--
-- See: https://hasura.io/docs/latest/graphql/core/auth/authentication/unauthenticated-access.html
data AuthMode
= AMNoAuth
| AMAdminSecret !AdminSecretHash !(Maybe RoleName)
| AMAdminSecretAndHook !AdminSecretHash !AuthHook
| AMAdminSecretAndJWT !AdminSecretHash !JWTCtx !(Maybe RoleName)
deriving (Show, Eq)
-- | Validate the user's requested authentication configuration, launching any
-- required maintenance threads for JWT etc.
--
-- This must only be run once, on launch.
setupAuthMode
:: ( HasVersion
, ForkableMonadIO m
, Tracing.HasReporter m
)
=> Maybe AdminSecretHash
-> Maybe AuthHook
-> Maybe JWTConfig
-> Maybe RoleName
-> H.Manager
-> Logger Hasura
-> ExceptT Text (ManagedT m) AuthMode
setupAuthMode mAdminSecretHash mWebHook mJwtSecret mUnAuthRole httpManager logger =
case (mAdminSecretHash, mWebHook, mJwtSecret) of
(Just hash, Nothing, Nothing) -> return $ AMAdminSecret hash mUnAuthRole
(Just hash, Nothing, Just jwtConf) -> do
jwtCtx <- mkJwtCtx jwtConf
return $ AMAdminSecretAndJWT hash jwtCtx mUnAuthRole
-- Nothing below this case uses unauth role. Throw a fatal error if we would otherwise ignore
-- that parameter, lest users misunderstand their auth configuration:
_ | isJust mUnAuthRole -> throwError $
"Fatal Error: --unauthorized-role (HASURA_GRAPHQL_UNAUTHORIZED_ROLE)"
<> requiresAdminScrtMsg
<> " and is not allowed when --auth-hook (HASURA_GRAPHQL_AUTH_HOOK) is set"
(Nothing, Nothing, Nothing) -> return AMNoAuth
(Just hash, Just hook, Nothing) -> return $ AMAdminSecretAndHook hash hook
(Nothing, Just _, Nothing) -> throwError $
"Fatal Error : --auth-hook (HASURA_GRAPHQL_AUTH_HOOK)" <> requiresAdminScrtMsg
(Nothing, Nothing, Just _) -> throwError $
"Fatal Error : --jwt-secret (HASURA_GRAPHQL_JWT_SECRET)" <> requiresAdminScrtMsg
(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
requiresAdminScrtMsg =
" requires --admin-secret (HASURA_GRAPHQL_ADMIN_SECRET) or "
<> " --access-key (HASURA_GRAPHQL_ACCESS_KEY) to be set"
-- | Given the 'JWTConfig' (the user input of JWT configuration), create
-- the 'JWTCtx' (the runtime JWT config used)
-- mkJwtCtx :: HasVersion => JWTConfig -> m JWTCtx
mkJwtCtx
:: ( HasVersion
, ForkableMonadIO m
, Tracing.HasReporter m
)
=> JWTConfig
-> ExceptT Text (ManagedT m) JWTCtx
mkJwtCtx JWTConfig{..} = do
jwkRef <- case jcKeyOrUrl of
Left jwk -> liftIO $ newIORef (JWKSet [jwk])
Right url -> getJwkFromUrl url
let jwtHeader = fromMaybe JHAuthorization jcHeader
return $ JWTCtx jwkRef jcAudience jcIssuer jcClaims jcAllowedSkew jwtHeader
where
-- if we can't find any expiry time for the JWK (either in @Expires@ header or @Cache-Control@
-- header), do not start a background thread for refreshing the JWK
getJwkFromUrl url = do
ref <- liftIO $ newIORef $ JWKSet []
maybeExpiry <- hoist lift $ withJwkError $ Tracing.runTraceT "jwk init" $ updateJwkRef logger httpManager url ref
case maybeExpiry of
Nothing -> return ref
Just time -> do
void . lift $ forkManagedT "jwkRefreshCtrl" logger $
jwkRefreshCtrl logger httpManager url ref (convertDuration time)
return ref
withJwkError act = do
res <- runExceptT act
onLeft res $ \case
-- when fetching JWK initially, except expiry parsing error, all errors are critical
JFEHttpException _ msg -> throwError msg
JFEHttpError _ _ _ e -> throwError e
JFEJwkParseError _ e -> throwError e
JFEExpiryParseError _ _ -> return Nothing
-- | Authenticate the request using the headers and the configured 'AuthMode'.
getUserInfoWithExpTime
:: forall m. (HasVersion, MonadIO m, MonadBaseControl IO m, MonadError QErr m, Tracing.MonadTrace m)
=> Logger Hasura
-> H.Manager
-> [N.Header]
-> AuthMode
-> Maybe ReqsText
-> m (UserInfo, Maybe UTCTime)
getUserInfoWithExpTime = getUserInfoWithExpTime_ userInfoFromAuthHook processJwt
-- Broken out for testing with mocks:
getUserInfoWithExpTime_
:: forall m _Manager _Logger_Hasura. (MonadIO m, MonadError QErr m)
[Preview] Inherited roles for postgres read queries fixes #3868 docker image - `hasura/graphql-engine:inherited-roles-preview-48b73a2de` Note: To be able to use the inherited roles feature, the graphql-engine should be started with the env variable `HASURA_GRAPHQL_EXPERIMENTAL_FEATURES` set to `inherited_roles`. Introduction ------------ This PR implements the idea of multiple roles as presented in this [paper](https://www.microsoft.com/en-us/research/wp-content/uploads/2016/02/FGALanguageICDE07.pdf). The multiple roles feature in this PR can be used via inherited roles. An inherited role is a role which can be created by combining multiple singular roles. For example, if there are two roles `author` and `editor` configured in the graphql-engine, then we can create a inherited role with the name of `combined_author_editor` role which will combine the select permissions of the `author` and `editor` roles and then make GraphQL queries using the `combined_author_editor`. How are select permissions of different roles are combined? ------------------------------------------------------------ A select permission includes 5 things: 1. Columns accessible to the role 2. Row selection filter 3. Limit 4. Allow aggregation 5. Scalar computed fields accessible to the role Suppose there are two roles, `role1` gives access to the `address` column with row filter `P1` and `role2` gives access to both the `address` and the `phone` column with row filter `P2` and we create a new role `combined_roles` which combines `role1` and `role2`. Let's say the following GraphQL query is queried with the `combined_roles` role. ```graphql query { employees { address phone } } ``` This will translate to the following SQL query: ```sql select (case when (P1 or P2) then address else null end) as address, (case when P2 then phone else null end) as phone from employee where (P1 or P2) ``` The other parameters of the select permission will be combined in the following manner: 1. Limit - Minimum of the limits will be the limit of the inherited role 2. Allow aggregations - If any of the role allows aggregation, then the inherited role will allow aggregation 3. Scalar computed fields - same as table column fields, as in the above example APIs for inherited roles: ---------------------- 1. `add_inherited_role` `add_inherited_role` is the [metadata API](https://hasura.io/docs/1.0/graphql/core/api-reference/index.html#schema-metadata-api) to create a new inherited role. It accepts two arguments `role_name`: the name of the inherited role to be added (String) `role_set`: list of roles that need to be combined (Array of Strings) Example: ```json { "type": "add_inherited_role", "args": { "role_name":"combined_user", "role_set":[ "user", "user1" ] } } ``` After adding the inherited role, the inherited role can be used like single roles like earlier Note: An inherited role can only be created with non-inherited/singular roles. 2. `drop_inherited_role` The `drop_inherited_role` API accepts the name of the inherited role and drops it from the metadata. It accepts a single argument: `role_name`: name of the inherited role to be dropped Example: ```json { "type": "drop_inherited_role", "args": { "role_name":"combined_user" } } ``` Metadata --------- The derived roles metadata will be included under the `experimental_features` key while exporting the metadata. ```json { "experimental_features": { "derived_roles": [ { "role_name": "manager_is_employee_too", "role_set": [ "employee", "manager" ] } ] } } ``` Scope ------ Only postgres queries and subscriptions are supported in this PR. Important points: ----------------- 1. All columns exposed to an inherited role will be marked as `nullable`, this is done so that cell value nullification can be done. TODOs ------- - [ ] Tests - [ ] Test a GraphQL query running with a inherited role without enabling inherited roles in experimental features - [] Tests for aggregate queries, limit, computed fields, functions, subscriptions (?) - [ ] Introspection test with a inherited role (nullability changes in a inherited role) - [ ] Docs - [ ] Changelog Co-authored-by: Vamshi Surabhi <6562944+0x777@users.noreply.github.com> GitOrigin-RevId: 3b8ee1e11f5ceca80fe294f8c074d42fbccfec63
2021-03-08 14:14:13 +03:00
=> (_Logger_Hasura -> _Manager -> AuthHook -> [N.Header]
-> Maybe ReqsText -> m (UserInfo, Maybe UTCTime))
-- ^ mock 'userInfoFromAuthHook'
-> (JWTCtx -> [N.Header] -> Maybe RoleName -> m (UserInfo, Maybe UTCTime))
-- ^ mock 'processJwt'
-> _Logger_Hasura
-> _Manager
-> [N.Header]
-> AuthMode
-> Maybe ReqsText
-> m (UserInfo, Maybe UTCTime)
[Preview] Inherited roles for postgres read queries fixes #3868 docker image - `hasura/graphql-engine:inherited-roles-preview-48b73a2de` Note: To be able to use the inherited roles feature, the graphql-engine should be started with the env variable `HASURA_GRAPHQL_EXPERIMENTAL_FEATURES` set to `inherited_roles`. Introduction ------------ This PR implements the idea of multiple roles as presented in this [paper](https://www.microsoft.com/en-us/research/wp-content/uploads/2016/02/FGALanguageICDE07.pdf). The multiple roles feature in this PR can be used via inherited roles. An inherited role is a role which can be created by combining multiple singular roles. For example, if there are two roles `author` and `editor` configured in the graphql-engine, then we can create a inherited role with the name of `combined_author_editor` role which will combine the select permissions of the `author` and `editor` roles and then make GraphQL queries using the `combined_author_editor`. How are select permissions of different roles are combined? ------------------------------------------------------------ A select permission includes 5 things: 1. Columns accessible to the role 2. Row selection filter 3. Limit 4. Allow aggregation 5. Scalar computed fields accessible to the role Suppose there are two roles, `role1` gives access to the `address` column with row filter `P1` and `role2` gives access to both the `address` and the `phone` column with row filter `P2` and we create a new role `combined_roles` which combines `role1` and `role2`. Let's say the following GraphQL query is queried with the `combined_roles` role. ```graphql query { employees { address phone } } ``` This will translate to the following SQL query: ```sql select (case when (P1 or P2) then address else null end) as address, (case when P2 then phone else null end) as phone from employee where (P1 or P2) ``` The other parameters of the select permission will be combined in the following manner: 1. Limit - Minimum of the limits will be the limit of the inherited role 2. Allow aggregations - If any of the role allows aggregation, then the inherited role will allow aggregation 3. Scalar computed fields - same as table column fields, as in the above example APIs for inherited roles: ---------------------- 1. `add_inherited_role` `add_inherited_role` is the [metadata API](https://hasura.io/docs/1.0/graphql/core/api-reference/index.html#schema-metadata-api) to create a new inherited role. It accepts two arguments `role_name`: the name of the inherited role to be added (String) `role_set`: list of roles that need to be combined (Array of Strings) Example: ```json { "type": "add_inherited_role", "args": { "role_name":"combined_user", "role_set":[ "user", "user1" ] } } ``` After adding the inherited role, the inherited role can be used like single roles like earlier Note: An inherited role can only be created with non-inherited/singular roles. 2. `drop_inherited_role` The `drop_inherited_role` API accepts the name of the inherited role and drops it from the metadata. It accepts a single argument: `role_name`: name of the inherited role to be dropped Example: ```json { "type": "drop_inherited_role", "args": { "role_name":"combined_user" } } ``` Metadata --------- The derived roles metadata will be included under the `experimental_features` key while exporting the metadata. ```json { "experimental_features": { "derived_roles": [ { "role_name": "manager_is_employee_too", "role_set": [ "employee", "manager" ] } ] } } ``` Scope ------ Only postgres queries and subscriptions are supported in this PR. Important points: ----------------- 1. All columns exposed to an inherited role will be marked as `nullable`, this is done so that cell value nullification can be done. TODOs ------- - [ ] Tests - [ ] Test a GraphQL query running with a inherited role without enabling inherited roles in experimental features - [] Tests for aggregate queries, limit, computed fields, functions, subscriptions (?) - [ ] Introspection test with a inherited role (nullability changes in a inherited role) - [ ] Docs - [ ] Changelog Co-authored-by: Vamshi Surabhi <6562944+0x777@users.noreply.github.com> GitOrigin-RevId: 3b8ee1e11f5ceca80fe294f8c074d42fbccfec63
2021-03-08 14:14:13 +03:00
getUserInfoWithExpTime_ userInfoFromAuthHook_ processJwt_ logger manager rawHeaders authMode reqs = case authMode of
2020-05-05 22:57:17 +03:00
AMNoAuth -> withNoExpTime $ mkUserInfoFallbackAdminRole UAuthNotSet
-- If hasura was started with an admin secret we:
-- - check if a secret was sent in the request
-- - if so, check it and authorize as admin else fail
-- - if not proceed with either webhook or JWT auth if configured
AMAdminSecret realAdminSecretHash maybeUnauthRole ->
checkingSecretIfSent realAdminSecretHash $ withNoExpTime $
2020-05-05 22:57:17 +03:00
-- Consider unauthorized role, if not found raise admin secret header required exception
case maybeUnauthRole of
Nothing -> throw401 $ adminSecretHeader <> "/"
<> deprecatedAccessKeyHeader <> " required, but not found"
Just unAuthRole ->
mkUserInfo (URBPreDetermined unAuthRole) UAdminSecretNotSent sessionVariables
-- this is the case that actually ends up consuming the request AST
AMAdminSecretAndHook realAdminSecretHash hook ->
checkingSecretIfSent realAdminSecretHash $ userInfoFromAuthHook_ logger manager hook rawHeaders reqs
add support for jwt authorization (close #186) (#255) The API: 1. HGE has `--jwt-secret` flag or `HASURA_GRAPHQL_JWT_SECRET` env var. The value of which is a JSON. 2. The structure of this JSON is: `{"type": "<standard-JWT-algorithms>", "key": "<the-key>"}` `type` : Standard JWT algos : `HS256`, `RS256`, `RS512` etc. (see jwt.io). `key`: i. Incase of symmetric key, the key as it is. ii. Incase of asymmetric keys, only the public key, in a PEM encoded string or as a X509 certificate. 3. The claims in the JWT token must contain the following: i. `x-hasura-default-role` field: default role of that user ii. `x-hasura-allowed-roles` : A list of allowed roles for the user. The default role is overriden by `x-hasura-role` header. 4. The claims in the JWT token, can have other `x-hasura-*` fields where their values can only be strings. 5. The JWT tokens are sent as `Authorization: Bearer <token>` headers. --- To test: 1. Generate a shared secret (for HMAC-SHA256) or RSA key pair. 2. Goto https://jwt.io/ , add the keys 3. Edit the claims to have `x-hasura-role` (mandatory) and other `x-hasura-*` fields. Add permissions related to the claims to test permissions. 4. Start HGE with `--jwt-secret` flag or `HASURA_GRAPHQL_JWT_SECRET` env var, which takes a JSON string: `{"type": "HS256", "key": "mylongsharedsecret"}` or `{"type":"RS256", "key": "<PEM-encoded-public-key>"}` 5. Copy the JWT token from jwt.io and use it in the `Authorization: Bearer <token>` header. --- TODO: Support EC public keys. It is blocked on frasertweedale/hs-jose#61
2018-08-30 13:32:09 +03:00
AMAdminSecretAndJWT realAdminSecretHash jwtSecret unAuthRole ->
checkingSecretIfSent realAdminSecretHash $ processJwt_ jwtSecret rawHeaders unAuthRole
where
-- CAREFUL!:
2020-05-05 22:57:17 +03:00
mkUserInfoFallbackAdminRole adminSecretState =
mkUserInfo (URBFromSessionVariablesFallback adminRoleName)
adminSecretState sessionVariables
sessionVariables = mkSessionVariablesHeaders rawHeaders
checkingSecretIfSent
:: AdminSecretHash -> m (UserInfo, Maybe UTCTime) -> m (UserInfo, Maybe UTCTime)
checkingSecretIfSent realAdminSecretHash actionIfNoAdminSecret = do
2020-05-05 22:57:17 +03:00
let maybeRequestAdminSecret =
foldl1 (<|>) $ map (`getSessionVariableValue` sessionVariables)
[adminSecretHeader, deprecatedAccessKeyHeader]
-- when admin secret is absent, run the action to retrieve UserInfo
case maybeRequestAdminSecret of
Nothing -> actionIfNoAdminSecret
Just requestAdminSecret -> do
when (hashAdminSecret requestAdminSecret /= realAdminSecretHash) $ throw401 $
2020-05-05 22:57:17 +03:00
"invalid " <> adminSecretHeader <> "/" <> deprecatedAccessKeyHeader
withNoExpTime $ mkUserInfoFallbackAdminRole UAdminSecretSent
withNoExpTime a = (, Nothing) <$> a