graphql-engine/server/src-lib/Hasura/Db.hs

236 lines
7.8 KiB
Haskell
Raw Normal View History

{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE UndecidableInstances #-}
2019-04-17 12:48:41 +03:00
-- A module for postgres execution related types and operations
module Hasura.Db
( MonadTx(..)
, LazyTx
, PGExecCtx(..)
, mkPGExecCtx
2019-04-17 12:48:41 +03:00
, runLazyTx
, runQueryTx
2019-04-17 12:48:41 +03:00
, withUserInfo
, sessionInfoJsonExp
2019-04-17 12:48:41 +03:00
, RespTx
, LazyRespTx
, defaultTxErrorHandler
, mkTxErrorHandler
2019-04-17 12:48:41 +03:00
) where
import Control.Lens
import Control.Monad.Trans.Control (MonadBaseControl (..))
import Control.Monad.Unique
import Control.Monad.Validate
import Data.Either (isRight)
import qualified Data.Aeson.Extended as J
import qualified Database.PG.Query as Q
import qualified Database.PG.Query.Connection as Q
2019-04-17 12:48:41 +03:00
import Hasura.EncJSON
import Hasura.Prelude
import Hasura.RQL.Types.Error
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
import Hasura.SQL.Error
2019-04-17 12:48:41 +03:00
import Hasura.SQL.Types
import qualified Hasura.SQL.DML as S
2019-04-17 12:48:41 +03:00
data PGExecCtx
= PGExecCtx
{ _pecRunReadOnly :: (forall a. Q.TxE QErr a -> ExceptT QErr IO a)
-- ^ Run a Q.ReadOnly transaction
, _pecRunReadNoTx :: (forall a. Q.TxE QErr a -> ExceptT QErr IO a)
-- ^ Run a read only statement without an explicit transaction block
, _pecRunReadWrite :: (forall a. Q.TxE QErr a -> ExceptT QErr IO a)
-- ^ Run a Q.ReadWrite transaction
, _pecCheckHealth :: (IO Bool)
-- ^ Checks the health of this execution context
2019-04-17 12:48:41 +03:00
}
-- | Creates a Postgres execution context for a single Postgres master pool
mkPGExecCtx :: Q.TxIsolation -> Q.PGPool -> PGExecCtx
mkPGExecCtx isoLevel pool =
PGExecCtx
{ _pecRunReadOnly = (Q.runTx pool (isoLevel, Just Q.ReadOnly))
, _pecRunReadNoTx = (Q.runTx' pool)
, _pecRunReadWrite = (Q.runTx pool (isoLevel, Just Q.ReadWrite))
, _pecCheckHealth = checkDbConnection
}
where
checkDbConnection = do
e <- liftIO $ runExceptT $ Q.runTx' pool select1Query
pure $ isRight e
where
select1Query :: Q.TxE QErr Int
select1Query =
runIdentity . Q.getRow <$>
Q.withQE defaultTxErrorHandler [Q.sql| SELECT 1 |] () False
2019-04-17 12:48:41 +03:00
class (MonadError QErr m) => MonadTx m where
liftTx :: Q.TxE QErr a -> m a
instance (MonadTx m) => MonadTx (StateT s m) where
liftTx = lift . liftTx
instance (MonadTx m) => MonadTx (ReaderT s m) where
liftTx = lift . liftTx
instance (Monoid w, MonadTx m) => MonadTx (WriterT w m) where
liftTx = lift . liftTx
instance (MonadTx m) => MonadTx (ValidateT e m) where
liftTx = lift . liftTx
2019-04-17 12:48:41 +03:00
-- | Like 'Q.TxE', but defers acquiring a Postgres connection until the first
-- execution of 'liftTx'. If no call to 'liftTx' is ever reached (i.e. a
-- successful result is returned or an error is raised before ever executing a
-- query), no connection is ever acquired.
--
-- This is useful for certain code paths that only conditionally need database
-- access. For example, although most queries will eventually hit Postgres,
-- introspection queries or queries that exclusively use remote schemas never
-- will; using 'LazyTx' keeps those branches from unnecessarily allocating a
-- connection.
2019-04-17 12:48:41 +03:00
data LazyTx e a
= LTErr !e
| LTNoTx !a
| LTTx !(Q.TxE e a)
deriving Show
-- orphan:
instance Show (Q.TxE e a) where
show = const "(error \"TxE\")"
2019-04-17 12:48:41 +03:00
lazyTxToQTx :: LazyTx e a -> Q.TxE e a
lazyTxToQTx = \case
LTErr e -> throwError e
LTNoTx r -> return r
LTTx tx -> tx
runLazyTx
:: (MonadIO m)
=> PGExecCtx
-> Q.TxAccess
-> LazyTx QErr a -> ExceptT QErr m a
runLazyTx pgExecCtx txAccess = \case
2019-04-17 12:48:41 +03:00
LTErr e -> throwError e
LTNoTx a -> return a
LTTx tx ->
case txAccess of
Q.ReadOnly -> ExceptT <$> liftIO $ runExceptT $ _pecRunReadOnly pgExecCtx tx
Q.ReadWrite -> ExceptT <$> liftIO $ runExceptT $ _pecRunReadWrite pgExecCtx tx
-- | This runs the given set of statements (Tx) without wrapping them in BEGIN
-- and COMMIT. This should only be used for running a single statement query!
runQueryTx
:: MonadIO m => PGExecCtx -> LazyTx QErr a -> ExceptT QErr m a
runQueryTx pgExecCtx = \case
2019-04-17 12:48:41 +03:00
LTErr e -> throwError e
LTNoTx a -> return a
LTTx tx -> ExceptT <$> liftIO $ runExceptT $ _pecRunReadNoTx pgExecCtx tx
2019-04-17 12:48:41 +03:00
type RespTx = Q.TxE QErr EncJSON
type LazyRespTx = LazyTx QErr EncJSON
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
setHeadersTx :: SessionVariables -> Q.TxE QErr ()
setHeadersTx session = do
2019-04-17 12:48:41 +03:00
Q.unitQE defaultTxErrorHandler setSess () False
where
setSess = Q.fromText $
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
"SET LOCAL \"hasura.user\" = " <> toSQLTxt (sessionInfoJsonExp session)
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
sessionInfoJsonExp :: SessionVariables -> S.SQLExp
sessionInfoJsonExp = S.SELit . J.encodeToStrictText
2019-04-17 12:48:41 +03:00
defaultTxErrorHandler :: Q.PGTxErr -> QErr
defaultTxErrorHandler = mkTxErrorHandler (const False)
-- | Constructs a transaction error handler given a predicate that determines which errors are
-- expected and should be reported to the user. All other errors are considered internal errors.
mkTxErrorHandler :: (PGErrorType -> Bool) -> Q.PGTxErr -> QErr
mkTxErrorHandler isExpectedError txe = fromMaybe unexpectedError expectedError
where
unexpectedError = (internalError "database query error") { qeInternal = Just $ J.toJSON txe }
expectedError = uncurry err400 <$> do
errorDetail <- Q.getPGStmtErr txe
message <- Q.edMessage errorDetail
errorType <- pgErrorType errorDetail
guard $ isExpectedError errorType
pure $ case errorType of
PGIntegrityConstraintViolation code ->
let cv = (ConstraintViolation,)
customMessage = (code ^? _Just._PGErrorSpecific) <&> \case
PGRestrictViolation -> cv "Can not delete or update due to data being referred. "
PGNotNullViolation -> cv "Not-NULL violation. "
PGForeignKeyViolation -> cv "Foreign key violation. "
PGUniqueViolation -> cv "Uniqueness violation. "
PGCheckViolation -> (PermissionError, "Check constraint violation. ")
PGExclusionViolation -> cv "Exclusion violation. "
in maybe (ConstraintViolation, message) (fmap (<> message)) customMessage
PGDataException code -> case code of
Just (PGErrorSpecific PGInvalidEscapeSequence) -> (BadRequest, message)
_ -> (DataException, message)
PGSyntaxErrorOrAccessRuleViolation code -> (ConstraintError,) $ case code of
Just (PGErrorSpecific PGInvalidColumnReference) ->
"there is no unique or exclusion constraint on target column(s)"
_ -> message
2019-04-17 12:48:41 +03:00
withUserInfo :: UserInfo -> LazyTx QErr a -> LazyTx QErr a
withUserInfo uInfo = \case
LTErr e -> LTErr e
LTNoTx a -> LTNoTx a
LTTx tx ->
let vars = _uiSession uInfo
in LTTx $ setHeadersTx vars >> tx
2019-04-17 12:48:41 +03:00
instance Functor (LazyTx e) where
fmap f = \case
LTErr e -> LTErr e
LTNoTx a -> LTNoTx $ f a
LTTx tx -> LTTx $ fmap f tx
instance Applicative (LazyTx e) where
pure = LTNoTx
LTErr e <*> _ = LTErr e
LTNoTx f <*> r = fmap f r
LTTx _ <*> LTErr e = LTErr e
LTTx txf <*> LTNoTx a = LTTx $ txf <*> pure a
LTTx txf <*> LTTx tx = LTTx $ txf <*> tx
instance Monad (LazyTx e) where
LTErr e >>= _ = LTErr e
LTNoTx a >>= f = f a
LTTx txa >>= f =
LTTx $ txa >>= lazyTxToQTx . f
instance MonadError e (LazyTx e) where
throwError = LTErr
LTErr e `catchError` f = f e
LTNoTx a `catchError` _ = LTNoTx a
LTTx txe `catchError` f =
LTTx $ txe `catchError` (lazyTxToQTx . f)
instance MonadTx (LazyTx QErr) where
liftTx = LTTx
instance MonadTx (Q.TxE QErr) where
liftTx = id
instance MonadIO (LazyTx e) where
2019-04-17 12:48:41 +03:00
liftIO = LTTx . liftIO
instance MonadBase IO (LazyTx e) where
liftBase = liftIO
instance MonadBaseControl IO (LazyTx e) where
type StM (LazyTx e) a = StM (Q.TxE e) a
liftBaseWith f = LTTx $ liftBaseWith \run -> f (run . lazyTxToQTx)
restoreM = LTTx . restoreM
instance MonadUnique (LazyTx e) where
newUnique = liftIO newUnique