2018-06-27 16:11:32 +03:00
|
|
|
|
module Hasura.GraphQL.Resolve.BoolExp
|
|
|
|
|
( parseBoolExp
|
2020-02-13 20:38:23 +03:00
|
|
|
|
, pgColValToBoolExp
|
2018-06-27 16:11:32 +03:00
|
|
|
|
) where
|
|
|
|
|
|
|
|
|
|
import Data.Has
|
|
|
|
|
import Hasura.Prelude
|
|
|
|
|
|
2019-07-15 11:52:45 +03:00
|
|
|
|
import qualified Data.HashMap.Strict as Map
|
2018-10-12 13:36:47 +03:00
|
|
|
|
import qualified Data.HashMap.Strict.InsOrd as OMap
|
2018-06-27 16:11:32 +03:00
|
|
|
|
import qualified Language.GraphQL.Draft.Syntax as G
|
|
|
|
|
|
|
|
|
|
import Hasura.GraphQL.Resolve.Context
|
|
|
|
|
import Hasura.GraphQL.Resolve.InputValue
|
|
|
|
|
import Hasura.GraphQL.Validate.Types
|
|
|
|
|
import Hasura.RQL.Types
|
2019-03-25 15:29:52 +03:00
|
|
|
|
import Hasura.SQL.Types
|
2019-07-10 13:19:58 +03:00
|
|
|
|
import Hasura.SQL.Value
|
|
|
|
|
|
|
|
|
|
import qualified Hasura.SQL.DML as S
|
2018-06-27 16:11:32 +03:00
|
|
|
|
|
2019-07-10 13:19:58 +03:00
|
|
|
|
type OpExp = OpExpG UnresolvedVal
|
2018-11-16 15:40:23 +03:00
|
|
|
|
|
2019-10-16 17:33:34 +03:00
|
|
|
|
parseOpExps :: (MonadReusability m, MonadError QErr m) => PGColumnType -> AnnInpVal -> m [OpExp]
|
2019-03-25 15:29:52 +03:00
|
|
|
|
parseOpExps colTy annVal = do
|
2018-06-27 16:11:32 +03:00
|
|
|
|
opExpsM <- flip withObjectM annVal $ \nt objM -> forM objM $ \obj ->
|
2019-04-17 12:48:41 +03:00
|
|
|
|
forM (OMap.toList obj) $ \(k, v) ->
|
2019-03-25 15:29:52 +03:00
|
|
|
|
case k of
|
2019-07-15 11:52:45 +03:00
|
|
|
|
"_cast" -> fmap ACast <$> parseCastExpression v
|
|
|
|
|
|
2019-07-10 13:19:58 +03:00
|
|
|
|
"_eq" -> fmap (AEQ True) <$> asOpRhs v
|
|
|
|
|
"_ne" -> fmap (ANE True) <$> asOpRhs v
|
|
|
|
|
"_neq" -> fmap (ANE True) <$> asOpRhs v
|
2019-03-25 15:29:52 +03:00
|
|
|
|
"_is_null" -> resolveIsNull v
|
2018-06-27 16:11:32 +03:00
|
|
|
|
|
2019-07-10 13:19:58 +03:00
|
|
|
|
"_in" -> fmap AIN <$> asPGArray colTy v
|
|
|
|
|
"_nin" -> fmap ANIN <$> asPGArray colTy v
|
2018-06-27 16:11:32 +03:00
|
|
|
|
|
2019-07-10 13:19:58 +03:00
|
|
|
|
"_gt" -> fmap AGT <$> asOpRhs v
|
|
|
|
|
"_lt" -> fmap ALT <$> asOpRhs v
|
|
|
|
|
"_gte" -> fmap AGTE <$> asOpRhs v
|
|
|
|
|
"_lte" -> fmap ALTE <$> asOpRhs v
|
2018-06-27 16:11:32 +03:00
|
|
|
|
|
2019-07-10 13:19:58 +03:00
|
|
|
|
"_like" -> fmap ALIKE <$> asOpRhs v
|
|
|
|
|
"_nlike" -> fmap ANLIKE <$> asOpRhs v
|
2018-06-27 16:11:32 +03:00
|
|
|
|
|
2019-07-10 13:19:58 +03:00
|
|
|
|
"_ilike" -> fmap AILIKE <$> asOpRhs v
|
|
|
|
|
"_nilike" -> fmap ANILIKE <$> asOpRhs v
|
2018-09-07 15:15:28 +03:00
|
|
|
|
|
2019-07-10 13:19:58 +03:00
|
|
|
|
"_similar" -> fmap ASIMILAR <$> asOpRhs v
|
|
|
|
|
"_nsimilar" -> fmap ANSIMILAR <$> asOpRhs v
|
2018-09-07 15:15:28 +03:00
|
|
|
|
|
|
|
|
|
-- jsonb related operators
|
2019-07-10 13:19:58 +03:00
|
|
|
|
"_contains" -> fmap AContains <$> asOpRhs v
|
|
|
|
|
"_contained_in" -> fmap AContainedIn <$> asOpRhs v
|
|
|
|
|
"_has_key" -> fmap AHasKey <$> asOpRhs v
|
|
|
|
|
|
2019-07-22 15:47:13 +03:00
|
|
|
|
"_has_keys_any" -> fmap AHasKeysAny <$> asPGArray (PGColumnScalar PGText) v
|
|
|
|
|
"_has_keys_all" -> fmap AHasKeysAll <$> asPGArray (PGColumnScalar PGText) v
|
2018-06-27 16:11:32 +03:00
|
|
|
|
|
2019-03-25 15:29:52 +03:00
|
|
|
|
-- geometry/geography type related operators
|
2019-07-10 13:19:58 +03:00
|
|
|
|
"_st_contains" -> fmap ASTContains <$> asOpRhs v
|
|
|
|
|
"_st_crosses" -> fmap ASTCrosses <$> asOpRhs v
|
|
|
|
|
"_st_equals" -> fmap ASTEquals <$> asOpRhs v
|
|
|
|
|
"_st_intersects" -> fmap ASTIntersects <$> asOpRhs v
|
|
|
|
|
"_st_overlaps" -> fmap ASTOverlaps <$> asOpRhs v
|
|
|
|
|
"_st_touches" -> fmap ASTTouches <$> asOpRhs v
|
|
|
|
|
"_st_within" -> fmap ASTWithin <$> asOpRhs v
|
2019-08-29 16:07:05 +03:00
|
|
|
|
"_st_d_within" -> parseAsObjectM v parseAsSTDWithinObj
|
|
|
|
|
|
|
|
|
|
-- raster type related operators
|
|
|
|
|
"_st_intersects_rast" -> fmap ASTIntersectsRast <$> asOpRhs v
|
|
|
|
|
"_st_intersects_nband_geom" -> parseAsObjectM v parseAsSTIntersectsNbandGeomObj
|
|
|
|
|
"_st_intersects_geom_nband" -> parseAsObjectM v parseAsSTIntersectsGeomNbandObj
|
2019-01-17 09:21:38 +03:00
|
|
|
|
|
2018-06-27 16:11:32 +03:00
|
|
|
|
_ ->
|
|
|
|
|
throw500
|
|
|
|
|
$ "unexpected operator found in opexp of "
|
|
|
|
|
<> showNamedTy nt
|
|
|
|
|
<> ": "
|
|
|
|
|
<> showName k
|
2018-11-16 15:40:23 +03:00
|
|
|
|
return $ catMaybes $ fromMaybe [] opExpsM
|
2018-07-12 17:03:02 +03:00
|
|
|
|
where
|
2019-09-14 09:01:06 +03:00
|
|
|
|
asOpRhs = fmap (fmap mkParameterizablePGValue) . asPGColumnValueM
|
2019-07-10 13:19:58 +03:00
|
|
|
|
|
2019-08-29 16:07:05 +03:00
|
|
|
|
parseAsObjectM v f = asObjectM v >>= mapM f
|
|
|
|
|
|
2019-07-10 13:19:58 +03:00
|
|
|
|
asPGArray rhsTy v = do
|
2019-09-14 09:01:06 +03:00
|
|
|
|
valsM <- parseMany (openOpaqueValue <=< asPGColumnValue) v
|
2019-07-10 13:19:58 +03:00
|
|
|
|
forM valsM $ \vals -> do
|
2019-07-22 15:47:13 +03:00
|
|
|
|
let arrayExp = S.SEArray $ map (txtEncoder . pstValue . _apvValue) vals
|
|
|
|
|
return $ UVSQL $ S.SETyAnn arrayExp $ S.mkTypeAnn $
|
|
|
|
|
-- Safe here because asPGColumnValue ensured all the values are of the right type, but if the
|
|
|
|
|
-- list is empty, we don’t actually have a scalar type to use, so we need to use
|
|
|
|
|
-- unsafePGColumnToRepresentation to create it. (It would be nice to refactor things to
|
|
|
|
|
-- somehow get rid of this.)
|
|
|
|
|
PGTypeArray (unsafePGColumnToRepresentation rhsTy)
|
2019-07-10 13:19:58 +03:00
|
|
|
|
|
2019-09-14 09:01:06 +03:00
|
|
|
|
resolveIsNull v = asPGColumnValueM v >>= traverse openOpaqueValue >>= \case
|
|
|
|
|
Nothing -> pure Nothing
|
|
|
|
|
Just annPGVal -> case pstValue $ _apvValue annPGVal of
|
|
|
|
|
PGValBoolean b -> pure . Just $ bool ANISNOTNULL ANISNULL b
|
|
|
|
|
_ -> throw500 "boolean value is expected"
|
2018-06-27 16:11:32 +03:00
|
|
|
|
|
2019-01-17 09:21:38 +03:00
|
|
|
|
parseAsSTDWithinObj obj = do
|
|
|
|
|
distanceVal <- onNothing (OMap.lookup "distance" obj) $
|
2019-03-25 15:29:52 +03:00
|
|
|
|
throw500 "expected \"distance\" input field in st_d_within"
|
2019-09-14 09:01:06 +03:00
|
|
|
|
dist <- mkParameterizablePGValue <$> asPGColumnValue distanceVal
|
2019-01-17 09:21:38 +03:00
|
|
|
|
fromVal <- onNothing (OMap.lookup "from" obj) $
|
2019-03-25 15:29:52 +03:00
|
|
|
|
throw500 "expected \"from\" input field in st_d_within"
|
2019-09-14 09:01:06 +03:00
|
|
|
|
from <- mkParameterizablePGValue <$> asPGColumnValue fromVal
|
2019-03-25 15:29:52 +03:00
|
|
|
|
case colTy of
|
2019-07-22 15:47:13 +03:00
|
|
|
|
PGColumnScalar PGGeography -> do
|
2019-07-10 13:19:58 +03:00
|
|
|
|
useSpheroidVal <-
|
|
|
|
|
onNothing (OMap.lookup "use_spheroid" obj) $
|
|
|
|
|
throw500 "expected \"use_spheroid\" input field in st_d_within"
|
2019-09-14 09:01:06 +03:00
|
|
|
|
useSpheroid <- mkParameterizablePGValue <$> asPGColumnValue useSpheroidVal
|
2019-03-25 15:29:52 +03:00
|
|
|
|
return $ ASTDWithinGeog $ DWithinGeogOp dist from useSpheroid
|
2019-07-22 15:47:13 +03:00
|
|
|
|
PGColumnScalar PGGeometry ->
|
2019-03-25 15:29:52 +03:00
|
|
|
|
return $ ASTDWithinGeom $ DWithinGeomOp dist from
|
|
|
|
|
_ -> throw500 "expected PGGeometry/PGGeography column for st_d_within"
|
2019-01-17 09:21:38 +03:00
|
|
|
|
|
2019-08-29 16:07:05 +03:00
|
|
|
|
parseAsSTIntersectsNbandGeomObj obj = do
|
|
|
|
|
nbandVal <- onNothing (OMap.lookup "nband" obj) $
|
|
|
|
|
throw500 "expected \"nband\" input field"
|
2019-09-14 09:01:06 +03:00
|
|
|
|
nband <- mkParameterizablePGValue <$> asPGColumnValue nbandVal
|
2019-08-29 16:07:05 +03:00
|
|
|
|
geommin <- parseGeommin obj
|
|
|
|
|
return $ ASTIntersectsNbandGeom $ STIntersectsNbandGeommin nband geommin
|
|
|
|
|
|
|
|
|
|
parseAsSTIntersectsGeomNbandObj obj = do
|
2019-09-14 09:01:06 +03:00
|
|
|
|
nbandMM <- fmap (fmap mkParameterizablePGValue) <$>
|
|
|
|
|
traverse asPGColumnValueM (OMap.lookup "nband" obj)
|
2019-08-29 16:07:05 +03:00
|
|
|
|
geommin <- parseGeommin obj
|
|
|
|
|
return $ ASTIntersectsGeomNband $ STIntersectsGeomminNband geommin $ join nbandMM
|
|
|
|
|
|
|
|
|
|
parseGeommin obj = do
|
|
|
|
|
geomminVal <- onNothing (OMap.lookup "geommin" obj) $
|
|
|
|
|
throw500 "expected \"geommin\" input field"
|
2019-09-14 09:01:06 +03:00
|
|
|
|
mkParameterizablePGValue <$> asPGColumnValue geomminVal
|
2019-08-29 16:07:05 +03:00
|
|
|
|
|
2019-07-15 11:52:45 +03:00
|
|
|
|
parseCastExpression
|
2019-10-16 17:33:34 +03:00
|
|
|
|
:: (MonadReusability m, MonadError QErr m)
|
2019-07-15 11:52:45 +03:00
|
|
|
|
=> AnnInpVal -> m (Maybe (CastExp UnresolvedVal))
|
|
|
|
|
parseCastExpression =
|
|
|
|
|
withObjectM $ \_ objM -> forM objM $ \obj -> do
|
|
|
|
|
targetExps <- forM (OMap.toList obj) $ \(targetTypeName, castedComparisonExpressionInput) -> do
|
2019-10-18 11:29:47 +03:00
|
|
|
|
let targetType = textToPGScalarType $ G.unName targetTypeName
|
2019-07-22 15:47:13 +03:00
|
|
|
|
castedComparisonExpressions <- parseOpExps (PGColumnScalar targetType) castedComparisonExpressionInput
|
2019-07-15 11:52:45 +03:00
|
|
|
|
return (targetType, castedComparisonExpressions)
|
|
|
|
|
return $ Map.fromList targetExps
|
|
|
|
|
|
2018-06-27 16:11:32 +03:00
|
|
|
|
parseColExp
|
2019-10-16 17:33:34 +03:00
|
|
|
|
:: ( MonadReusability m
|
|
|
|
|
, MonadError QErr m
|
2019-04-17 12:48:41 +03:00
|
|
|
|
, MonadReader r m
|
|
|
|
|
, Has FieldMap r
|
|
|
|
|
)
|
|
|
|
|
=> G.NamedType -> G.Name -> AnnInpVal
|
|
|
|
|
-> m (AnnBoolExpFld UnresolvedVal)
|
|
|
|
|
parseColExp nt n val = do
|
2018-06-27 16:11:32 +03:00
|
|
|
|
fldInfo <- getFldInfo nt n
|
|
|
|
|
case fldInfo of
|
2019-10-18 11:29:47 +03:00
|
|
|
|
RFPGColumn pgColInfo -> do
|
2019-03-25 15:29:52 +03:00
|
|
|
|
opExps <- parseOpExps (pgiType pgColInfo) val
|
2019-07-10 13:19:58 +03:00
|
|
|
|
return $ AVCol pgColInfo opExps
|
2019-10-18 11:29:47 +03:00
|
|
|
|
RFRelationship (RelationshipField relInfo _ _ permExp _)-> do
|
2019-04-17 12:48:41 +03:00
|
|
|
|
relBoolExp <- parseBoolExp val
|
|
|
|
|
return $ AVRel relInfo $ andAnnBoolExps relBoolExp $
|
|
|
|
|
fmapAnnBoolExp partialSQLExpToUnresolvedVal permExp
|
2019-10-18 11:29:47 +03:00
|
|
|
|
RFComputedField _ -> throw500
|
|
|
|
|
"computed fields are not allowed in bool_exp"
|
2018-06-27 16:11:32 +03:00
|
|
|
|
|
|
|
|
|
parseBoolExp
|
2019-10-16 17:33:34 +03:00
|
|
|
|
:: ( MonadReusability m
|
|
|
|
|
, MonadError QErr m
|
2019-04-17 12:48:41 +03:00
|
|
|
|
, MonadReader r m
|
|
|
|
|
, Has FieldMap r
|
|
|
|
|
)
|
|
|
|
|
=> AnnInpVal -> m (AnnBoolExp UnresolvedVal)
|
|
|
|
|
parseBoolExp annGVal = do
|
2018-06-27 16:11:32 +03:00
|
|
|
|
boolExpsM <-
|
|
|
|
|
flip withObjectM annGVal
|
2018-10-12 13:36:47 +03:00
|
|
|
|
$ \nt objM -> forM objM $ \obj -> forM (OMap.toList obj) $ \(k, v) -> if
|
2018-11-16 15:40:23 +03:00
|
|
|
|
| k == "_or" -> BoolOr . fromMaybe []
|
2019-04-17 12:48:41 +03:00
|
|
|
|
<$> parseMany parseBoolExp v
|
2018-11-16 15:40:23 +03:00
|
|
|
|
| k == "_and" -> BoolAnd . fromMaybe []
|
2019-04-17 12:48:41 +03:00
|
|
|
|
<$> parseMany parseBoolExp v
|
|
|
|
|
| k == "_not" -> BoolNot <$> parseBoolExp v
|
|
|
|
|
| otherwise -> BoolFld <$> parseColExp nt k v
|
2018-06-27 16:11:32 +03:00
|
|
|
|
return $ BoolAnd $ fromMaybe [] boolExpsM
|
2020-02-13 20:38:23 +03:00
|
|
|
|
|
|
|
|
|
type PGColValMap = Map.HashMap G.Name AnnInpVal
|
|
|
|
|
|
|
|
|
|
pgColValToBoolExp
|
|
|
|
|
:: (MonadReusability m, MonadError QErr m)
|
|
|
|
|
=> PGColArgMap -> PGColValMap -> m AnnBoolExpUnresolved
|
|
|
|
|
pgColValToBoolExp colArgMap colValMap = do
|
|
|
|
|
colExps <- forM colVals $ \(name, val) ->
|
|
|
|
|
BoolFld <$> do
|
|
|
|
|
opExp <- AEQ True . mkParameterizablePGValue <$> asPGColumnValue val
|
|
|
|
|
colInfo <- onNothing (Map.lookup name colArgMap) $
|
|
|
|
|
throw500 $ "column name " <> showName name
|
|
|
|
|
<> " not found in column arguments map"
|
|
|
|
|
return $ AVCol colInfo [opExp]
|
|
|
|
|
return $ BoolAnd colExps
|
|
|
|
|
where
|
|
|
|
|
colVals = Map.toList colValMap
|