fix input object validation logic (fix #693) (#711)

This commit is contained in:
Rakesh Emmadi 2018-10-12 16:06:47 +05:30 committed by Shahidh K Muhammed
parent ecf8c760ec
commit 37e848ccca
12 changed files with 101 additions and 31 deletions

View File

@ -15,6 +15,7 @@ import Data.Has
import Hasura.Prelude
import qualified Data.HashMap.Strict as Map
import qualified Data.HashMap.Strict.InsOrd as OMap
import qualified Language.GraphQL.Draft.Syntax as G
import qualified Hasura.RQL.GBoolExp as RA
@ -34,7 +35,7 @@ parseOpExps
=> AnnGValue -> m [RA.OpExp]
parseOpExps annVal = do
opExpsM <- flip withObjectM annVal $ \nt objM -> forM objM $ \obj ->
forM (Map.toList obj) $ \(k, v) -> case k of
forM (OMap.toList obj) $ \(k, v) -> case k of
"_eq" -> fmap RA.AEQ <$> asPGColValM v
"_ne" -> fmap RA.ANE <$> asPGColValM v
"_neq" -> fmap RA.ANE <$> asPGColValM v
@ -108,7 +109,7 @@ parseBoolExp
parseBoolExp annGVal = do
boolExpsM <-
flip withObjectM annGVal
$ \nt objM -> forM objM $ \obj -> forM (Map.toList obj) $ \(k, v) -> if
$ \nt objM -> forM objM $ \obj -> forM (OMap.toList obj) $ \(k, v) -> if
| k == "_or" -> BoolOr . fromMaybe [] <$> parseMany parseBoolExp v
| k == "_and" -> BoolAnd . fromMaybe [] <$> parseMany parseBoolExp v
| k == "_not" -> BoolNot <$> parseBoolExp v

View File

@ -14,6 +14,7 @@ import Hasura.Prelude
import qualified Data.Aeson as J
import qualified Data.ByteString.Builder as BB
import qualified Data.HashMap.Strict as Map
import qualified Data.HashMap.Strict.InsOrd as OMap
import qualified Data.HashSet as Set
import qualified Data.Sequence as Seq
import qualified Data.Text as T
@ -65,7 +66,7 @@ parseAction
:: (MonadError QErr m)
=> AnnGObject -> m (Maybe ConflictAction)
parseAction obj = withPathK "action" $
mapM parseVal $ Map.lookup "action" obj
mapM parseVal $ OMap.lookup "action" obj
where
parseVal val = do
(enumTy, enumVal) <- asEnumVal val
@ -80,7 +81,7 @@ parseConstraint
:: (MonadError QErr m)
=> AnnGObject -> m ConstraintName
parseConstraint obj = withPathK "constraint" $ do
v <- onNothing (Map.lookup "constraint" obj) $ throw500
v <- onNothing (OMap.lookup "constraint" obj) $ throw500
"\"constraint\" is expected, but not found"
parseVal v
where
@ -92,7 +93,7 @@ parseUpdCols
:: (MonadError QErr m)
=> AnnGObject -> m (Maybe [PGCol])
parseUpdCols obj = withPathK "update_columns" $
mapM parseVal $ Map.lookup "update_columns" obj
mapM parseVal $ OMap.lookup "update_columns" obj
where
parseVal val = flip withArray val $ \_ enumVals ->
forM enumVals $ \eVal -> do
@ -119,8 +120,8 @@ parseRelObj
=> AnnGObject
-> m (Either ObjRelData ArrRelData)
parseRelObj annObj = do
let conflictClauseM = Map.lookup "on_conflict" annObj
dataVal <- onNothing (Map.lookup "data" annObj) $ throw500 "\"data\" object not found"
let conflictClauseM = OMap.lookup "on_conflict" annObj
dataVal <- onNothing (OMap.lookup "data" annObj) $ throw500 "\"data\" object not found"
case dataVal of
AGObject _ (Just obj) -> return $ Left $ RelData obj conflictClauseM
AGArray _ (Just vals) -> do
@ -165,7 +166,7 @@ fetchColsAndRels
, [(RelName, ObjRelData)] -- ^ object relations
, [(RelName, ArrRelData)] -- ^ array relations
)
fetchColsAndRels annObj = foldrM go ([], [], []) $ Map.toList annObj
fetchColsAndRels annObj = foldrM go ([], [], []) $ OMap.toList annObj
where
go (gName, annVal) (cols, objRels, arrRels) =
case annVal of

View File

@ -12,7 +12,7 @@ module Hasura.GraphQL.Resolve.Mutation
import Hasura.Prelude
import qualified Data.HashMap.Strict as Map
import qualified Data.HashMap.Strict.InsOrd as OMap
import qualified Language.GraphQL.Draft.Syntax as G
import qualified Hasura.RQL.DML.Delete as RD
@ -61,7 +61,7 @@ convertRowObj
=> AnnGValue
-> m [(PGCol, S.SQLExp)]
convertRowObj val =
flip withObject val $ \_ obj -> forM (Map.toList obj) $ \(k, v) -> do
flip withObject val $ \_ obj -> forM (OMap.toList obj) $ \(k, v) -> do
prepExpM <- asPGColValM v >>= mapM prepare
let prepExp = fromMaybe (S.SEUnsafe "NULL") prepExpM
return (PGCol $ G.unName k, prepExp)
@ -84,7 +84,7 @@ convObjWithOp
:: (MonadError QErr m)
=> ApplySQLOp -> AnnGValue -> m [(PGCol, S.SQLExp)]
convObjWithOp opFn val =
flip withObject val $ \_ obj -> forM (Map.toList obj) $ \(k, v) -> do
flip withObject val $ \_ obj -> forM (OMap.toList obj) $ \(k, v) -> do
(_, colVal) <- asPGColVal v
let pgCol = PGCol $ G.unName k
encVal = txtEncoder colVal
@ -95,7 +95,7 @@ convDeleteAtPathObj
:: (MonadError QErr m)
=> AnnGValue -> m [(PGCol, S.SQLExp)]
convDeleteAtPathObj val =
flip withObject val $ \_ obj -> forM (Map.toList obj) $ \(k, v) -> do
flip withObject val $ \_ obj -> forM (OMap.toList obj) $ \(k, v) -> do
vals <- flip withArray v $ \_ annVals -> mapM asPGColVal annVals
let valExps = map (txtEncoder . snd) vals
pgCol = PGCol $ G.unName k

View File

@ -1,7 +1,8 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Hasura.GraphQL.Validate.InputValue
( validateInputValue
@ -12,11 +13,13 @@ module Hasura.GraphQL.Validate.InputValue
import Data.Scientific (fromFloatDigits)
import Hasura.Prelude
import Hasura.Server.Utils (duplicates)
import Data.Has
import qualified Data.Aeson as J
import qualified Data.HashMap.Strict as Map
import qualified Data.HashMap.Strict.InsOrd as OMap
import qualified Data.Vector as V
import qualified Language.GraphQL.Draft.Syntax as G
@ -168,26 +171,31 @@ validateObject
-> InpObjTyInfo -> [(G.Name, a)] -> m AnnGObject
validateObject valParser tyInfo flds = do
fldMap <- fmap (Map.map snd) $ onLeft (mkMapWith fst flds) $ \dups ->
-- check duplicates
unless (null dups) $
throwVE $ "when parsing a value of type: " <> showNamedTy (_iotiName tyInfo)
<> ", the following fields are duplicated: "
<> showNames dups
annFldsM <- forM (Map.toList $ _iotiFields tyInfo) $
-- check fields with not null types
forM_ (Map.toList $ _iotiFields tyInfo) $
\(fldName, inpValInfo) -> do
let fldValM = Map.lookup fldName fldMap
ty = _iviType inpValInfo
let ty = _iviType inpValInfo
isNotNull = G.isNotNull ty
when (isNothing fldValM && isNotNull) $ throwVE $
fldPresent = fldName `elem` inpFldNames
when (not fldPresent && isNotNull) $ throwVE $
"field " <> G.unName fldName <> " of type " <> G.showGT ty
<> " is required, but not found"
forM fldValM $ \fldVal ->
withPathK (G.unName fldName) $ do
fldTy <- getInpFieldInfo tyInfo fldName
convFldVal <- validateInputValue valParser fldTy fldVal
return (fldName, convFldVal)
return $ Map.fromList $ catMaybes annFldsM
fmap OMap.fromList $ forM flds $ \(fldName, fldVal) ->
withPathK (G.unName fldName) $ do
fldTy <- getInpFieldInfo tyInfo fldName
convFldVal <- validateInputValue valParser fldTy fldVal
return (fldName, convFldVal)
where
inpFldNames = map fst flds
dups = duplicates inpFldNames
validateNamedTypeVal
:: ( MonadReader r m, Has TypeMap r

View File

@ -48,6 +48,7 @@ import Hasura.Prelude
import qualified Data.Aeson as J
import qualified Data.HashMap.Strict as Map
import qualified Data.HashMap.Strict.InsOrd as OMap
import qualified Data.Text as T
import qualified Language.GraphQL.Draft.Syntax as G
import qualified Language.GraphQL.Draft.TH as G
@ -271,7 +272,7 @@ type FragDefMap = Map.HashMap G.Name FragDef
type AnnVarVals =
Map.HashMap G.Variable AnnGValue
type AnnGObject = Map.HashMap G.Name AnnGValue
type AnnGObject = OMap.InsOrdHashMap G.Name AnnGValue
data AnnGValue
= AGScalar !PGColType !(Maybe PGColValue)

View File

@ -5,15 +5,15 @@ module Hasura.Prelude
import Control.Applicative as M ((<|>))
import Control.Monad as M (void, when)
import Control.Monad.Except as M
import Control.Monad.Fail as M (MonadFail)
import Control.Monad.Identity as M
import Control.Monad.Reader as M
import Control.Monad.State as M
import Control.Monad.Fail as M (MonadFail)
import Data.Bool as M (bool)
import Data.Either as M (lefts, partitionEithers, rights)
import Data.Foldable as M (toList)
import Data.Hashable as M (Hashable)
import Data.List as M (find, foldl', group, sortBy)
import Data.List as M (find, foldl', group, sort, sortBy)
import Data.Maybe as M (catMaybes, fromMaybe, isJust,
isNothing, listToMaybe, mapMaybe,
maybeToList)

View File

@ -112,3 +112,9 @@ parseGingerTmplt src = either parseE Right res
renderGingerTmplt :: (ToJSON a) => a -> GingerTmplt -> T.Text
renderGingerTmplt v = TG.easyRender (toJSON v)
-- find duplicates
duplicates :: Ord a => [a] -> [a]
duplicates = mapMaybe greaterThanOne . group . sort
where
greaterThanOne l = bool Nothing (Just $ head l) $ length l > 1

View File

@ -0,0 +1,15 @@
description: Delete a row in resident table where id = 1 (Error)
url: /v1alpha1/graphql
status: 400
headers:
X-Hasura-Role: user
X-Hasura-User-Id: '1'
query:
query: |
mutation{
delete_resident(
where: {id: {_eq: 1}}
){
affected_rows
}
}

View File

@ -117,3 +117,34 @@ args:
filter:
$and:
- author_id: X-HASURA-USER-ID
#Create resident table
- type: run_sql
args:
sql: |
CREATE TABLE resident (
id SERIAL PRIMARY KEY,
name TEXT NOT NULL,
age INTEGER NOT NULL
)
- type: track_table
args:
schema: public
name: resident
- type: insert
args:
table: resident
objects:
- name: Griffin
age: 25
- name: Clarke
age: 26
- type: create_delete_permission
args:
table: resident
role: resident
permission:
filter:
id: X-Hasura-Resident-Id

View File

@ -16,3 +16,7 @@ args:
args:
sql: |
drop table author
- type: run_sql
args:
sql: |
drop table resident

View File

@ -3,7 +3,7 @@ url: /v1alpha1/graphql
headers:
X-Hasura-Role: user
X-Hasura-User-Id: '1'
status: 500
status: 400
query:
query: |
mutation update_article {

View File

@ -281,6 +281,9 @@ class TestGraphqlDeletePermissions:
def test_author_cannot_delete_other_users_articles(self, hge_ctx):
check_query_f(hge_ctx, self.dir + "/author_cannot_delete_other_users_articles.yaml")
def test_resident_delete_without_select_perm_fail(self, hge_ctx):
check_query_f(hge_ctx, self.dir + "/resident_delete_without_select_perm_fail.yaml")
@pytest.fixture(autouse=True)
def transact(self, request, hge_ctx):
self.dir = "queries/graphql_mutation/delete/permissions"