2018-06-27 16:11:32 +03:00
|
|
|
module Hasura.GraphQL.Resolve.Select
|
|
|
|
( convertSelect
|
2018-08-27 17:17:03 +03:00
|
|
|
, convertSelectByPKey
|
2018-10-26 12:02:44 +03:00
|
|
|
, convertAggSelect
|
2019-04-17 12:48:41 +03:00
|
|
|
, convertFuncQuerySimple
|
|
|
|
, convertFuncQueryAgg
|
2018-11-14 15:59:59 +03:00
|
|
|
, parseColumns
|
2020-02-13 20:38:23 +03:00
|
|
|
, processTableSelectionSet
|
|
|
|
, AnnSimpleSelect
|
2018-06-27 16:11:32 +03:00
|
|
|
) where
|
|
|
|
|
2019-12-27 01:32:48 +03:00
|
|
|
import Control.Lens ((^?), _2)
|
2018-06-27 16:11:32 +03:00
|
|
|
import Data.Has
|
2019-03-25 16:45:35 +03:00
|
|
|
import Data.Parser.JSONPath
|
2018-06-27 16:11:32 +03:00
|
|
|
import Hasura.Prelude
|
|
|
|
|
|
|
|
import qualified Data.HashMap.Strict as Map
|
2018-10-26 14:57:33 +03:00
|
|
|
import qualified Data.HashMap.Strict.InsOrd as OMap
|
|
|
|
import qualified Data.List.NonEmpty as NE
|
2019-11-20 09:47:06 +03:00
|
|
|
import qualified Data.Sequence as Seq
|
2018-12-12 15:58:39 +03:00
|
|
|
import qualified Data.Text as T
|
2018-06-27 16:11:32 +03:00
|
|
|
import qualified Language.GraphQL.Draft.Syntax as G
|
|
|
|
|
|
|
|
import qualified Hasura.RQL.DML.Select as RS
|
|
|
|
import qualified Hasura.SQL.DML as S
|
|
|
|
|
|
|
|
import Hasura.GraphQL.Resolve.BoolExp
|
|
|
|
import Hasura.GraphQL.Resolve.Context
|
|
|
|
import Hasura.GraphQL.Resolve.InputValue
|
2018-11-14 15:59:59 +03:00
|
|
|
import Hasura.GraphQL.Schema (isAggFld)
|
2018-06-27 16:11:32 +03:00
|
|
|
import Hasura.GraphQL.Validate.Field
|
|
|
|
import Hasura.GraphQL.Validate.Types
|
2018-08-06 15:15:08 +03:00
|
|
|
import Hasura.RQL.DML.Internal (onlyPositiveInt)
|
2018-06-27 16:11:32 +03:00
|
|
|
import Hasura.RQL.Types
|
|
|
|
import Hasura.SQL.Types
|
2018-08-06 15:15:08 +03:00
|
|
|
import Hasura.SQL.Value
|
2018-06-27 16:11:32 +03:00
|
|
|
|
2019-03-25 16:45:35 +03:00
|
|
|
jsonPathToColExp :: (MonadError QErr m) => T.Text -> m S.SQLExp
|
|
|
|
jsonPathToColExp t = case parseJSONPath t of
|
|
|
|
Left s -> throw400 ParseFailed $ T.pack $ "parse json path error: " ++ s
|
|
|
|
Right jPaths -> return $ S.SEArray $ map elToColExp jPaths
|
|
|
|
where
|
|
|
|
elToColExp (Key k) = S.SELit k
|
|
|
|
elToColExp (Index i) = S.SELit $ T.pack (show i)
|
|
|
|
|
|
|
|
|
2019-10-16 17:33:34 +03:00
|
|
|
argsToColOp :: (MonadReusability m, MonadError QErr m) => ArgsMap -> m (Maybe RS.ColOp)
|
2019-03-25 16:45:35 +03:00
|
|
|
argsToColOp args = maybe (return Nothing) toOp $ Map.lookup "path" args
|
|
|
|
where
|
|
|
|
toJsonPathExp = fmap (RS.ColOp S.jsonbPathOp) . jsonPathToColExp
|
2019-09-14 09:01:06 +03:00
|
|
|
toOp v = asPGColTextM v >>= traverse toJsonPathExp
|
2019-03-25 16:45:35 +03:00
|
|
|
|
2019-04-17 12:48:41 +03:00
|
|
|
type AnnFlds = RS.AnnFldsG UnresolvedVal
|
|
|
|
|
2019-10-18 11:29:47 +03:00
|
|
|
resolveComputedField
|
|
|
|
:: ( MonadReusability m, MonadReader r m, Has FieldMap r
|
|
|
|
, Has OrdByCtx r, Has SQLGenCtx r, MonadError QErr m
|
|
|
|
)
|
|
|
|
=> ComputedField -> Field -> m (RS.ComputedFieldSel UnresolvedVal)
|
|
|
|
resolveComputedField computedField fld = fieldAsPath fld $ do
|
2019-12-27 01:32:48 +03:00
|
|
|
funcArgs <- parseFunctionArgs argSeq argFn $ Map.lookup "args" $ _fArguments fld
|
|
|
|
let argsWithTableArgument = withTableArgument funcArgs
|
2019-10-18 11:29:47 +03:00
|
|
|
case fieldType of
|
|
|
|
CFTScalar scalarTy -> do
|
|
|
|
colOpM <- argsToColOp $ _fArguments fld
|
|
|
|
pure $ RS.CFSScalar $
|
|
|
|
RS.ComputedFieldScalarSel qf argsWithTableArgument scalarTy colOpM
|
|
|
|
CFTTable (ComputedFieldTable _ cols permFilter permLimit) -> do
|
2020-02-13 20:38:23 +03:00
|
|
|
let functionFrom = RS.FromFunction qf argsWithTableArgument Nothing
|
|
|
|
RS.CFSTable RS.JASMultipleRows <$> fromField functionFrom cols permFilter permLimit fld
|
2019-10-18 11:29:47 +03:00
|
|
|
where
|
|
|
|
ComputedField _ function argSeq fieldType = computedField
|
|
|
|
ComputedFieldFunction qf _ tableArg _ = function
|
2019-11-20 09:47:06 +03:00
|
|
|
argFn = IFAUnknown
|
2019-10-18 11:29:47 +03:00
|
|
|
withTableArgument resolvedArgs =
|
|
|
|
let argsExp@(RS.FunctionArgsExp positional named) = RS.AEInput <$> resolvedArgs
|
2020-02-13 20:38:23 +03:00
|
|
|
tableRowArg = RS.AETableRow Nothing
|
2019-10-18 11:29:47 +03:00
|
|
|
in case tableArg of
|
|
|
|
FTAFirst ->
|
2020-02-13 20:38:23 +03:00
|
|
|
RS.FunctionArgsExp (tableRowArg:positional) named
|
2019-10-18 11:29:47 +03:00
|
|
|
FTANamed argName index ->
|
2020-02-13 20:38:23 +03:00
|
|
|
RS.insertFunctionArg argName index tableRowArg argsExp
|
2019-10-18 11:29:47 +03:00
|
|
|
|
2020-02-13 20:38:23 +03:00
|
|
|
processTableSelectionSet
|
2019-10-16 17:33:34 +03:00
|
|
|
:: ( MonadReusability m, MonadError QErr m, MonadReader r m, Has FieldMap r
|
2019-03-01 14:45:04 +03:00
|
|
|
, Has OrdByCtx r, Has SQLGenCtx r
|
|
|
|
)
|
2019-04-17 12:48:41 +03:00
|
|
|
=> G.NamedType -> SelSet -> m AnnFlds
|
2020-02-13 20:38:23 +03:00
|
|
|
processTableSelectionSet fldTy flds =
|
2018-10-05 11:56:47 +03:00
|
|
|
forM (toList flds) $ \fld -> do
|
2018-06-27 16:11:32 +03:00
|
|
|
let fldName = _fName fld
|
|
|
|
let rqlFldName = FieldName $ G.unName $ G.unAlias $ _fAlias fld
|
2018-10-05 11:56:47 +03:00
|
|
|
(rqlFldName,) <$> case fldName of
|
|
|
|
"__typename" -> return $ RS.FExp $ G.unName $ G.unNamedType fldTy
|
2018-06-27 16:11:32 +03:00
|
|
|
_ -> do
|
|
|
|
fldInfo <- getFldInfo fldTy fldName
|
|
|
|
case fldInfo of
|
2019-10-18 11:29:47 +03:00
|
|
|
RFPGColumn colInfo ->
|
2019-11-07 08:14:36 +03:00
|
|
|
RS.mkAnnColField colInfo <$> argsToColOp (_fArguments fld)
|
2019-10-18 11:29:47 +03:00
|
|
|
RFComputedField computedField ->
|
|
|
|
RS.FComputedField <$> resolveComputedField computedField fld
|
|
|
|
RFRelationship (RelationshipField relInfo isAgg colGNameMap tableFilter tableLimit) -> do
|
2018-06-27 16:11:32 +03:00
|
|
|
let relTN = riRTable relInfo
|
2018-10-31 15:51:20 +03:00
|
|
|
colMapping = riMapping relInfo
|
2018-12-12 15:58:39 +03:00
|
|
|
rn = riName relInfo
|
2018-10-31 15:51:20 +03:00
|
|
|
if isAgg then do
|
2019-12-10 05:27:44 +03:00
|
|
|
aggSel <- fromAggField (RS.FromTable relTN) colGNameMap tableFilter tableLimit fld
|
2018-12-12 15:58:39 +03:00
|
|
|
return $ RS.FArr $ RS.ASAgg $ RS.AnnRelG rn colMapping aggSel
|
2018-10-31 15:51:20 +03:00
|
|
|
else do
|
2019-10-18 11:29:47 +03:00
|
|
|
annSel <- fromField (RS.FromTable relTN) colGNameMap tableFilter tableLimit fld
|
2018-12-12 15:58:39 +03:00
|
|
|
let annRel = RS.AnnRelG rn colMapping annSel
|
|
|
|
return $ case riType relInfo of
|
|
|
|
ObjRel -> RS.FObj annRel
|
|
|
|
ArrRel -> RS.FArr $ RS.ASSimple annRel
|
2018-06-27 16:11:32 +03:00
|
|
|
|
2019-04-17 12:48:41 +03:00
|
|
|
type TableAggFlds = RS.TableAggFldsG UnresolvedVal
|
|
|
|
|
2019-01-25 06:31:54 +03:00
|
|
|
fromAggSelSet
|
2019-10-16 17:33:34 +03:00
|
|
|
:: ( MonadReusability m, MonadError QErr m, MonadReader r m, Has FieldMap r
|
2019-03-01 14:45:04 +03:00
|
|
|
, Has OrdByCtx r, Has SQLGenCtx r
|
|
|
|
)
|
2019-09-19 07:47:36 +03:00
|
|
|
=> PGColGNameMap -> G.NamedType -> SelSet -> m TableAggFlds
|
|
|
|
fromAggSelSet colGNameMap fldTy selSet = fmap toFields $
|
2019-01-25 06:31:54 +03:00
|
|
|
withSelSet selSet $ \f -> do
|
|
|
|
let fTy = _fType f
|
|
|
|
fSelSet = _fSelSet f
|
|
|
|
case _fName f of
|
|
|
|
"__typename" -> return $ RS.TAFExp $ G.unName $ G.unNamedType fldTy
|
2019-09-19 07:47:36 +03:00
|
|
|
"aggregate" -> RS.TAFAgg <$> convertAggFld colGNameMap fTy fSelSet
|
2020-02-13 20:38:23 +03:00
|
|
|
"nodes" -> RS.TAFNodes <$> processTableSelectionSet fTy fSelSet
|
2019-01-25 06:31:54 +03:00
|
|
|
G.Name t -> throw500 $ "unexpected field in _agg node: " <> t
|
|
|
|
|
2019-04-17 12:48:41 +03:00
|
|
|
type TableArgs = RS.TableArgsG UnresolvedVal
|
2018-08-06 15:15:08 +03:00
|
|
|
|
2018-10-05 11:56:47 +03:00
|
|
|
parseTableArgs
|
2019-10-16 17:33:34 +03:00
|
|
|
:: ( MonadReusability m, MonadError QErr m, MonadReader r m
|
2019-03-01 14:45:04 +03:00
|
|
|
, Has FieldMap r, Has OrdByCtx r
|
|
|
|
)
|
2019-09-19 07:47:36 +03:00
|
|
|
=> PGColGNameMap -> ArgsMap -> m TableArgs
|
|
|
|
parseTableArgs colGNameMap args = do
|
2019-04-17 12:48:41 +03:00
|
|
|
whereExpM <- withArgM args "where" parseBoolExp
|
2018-10-26 14:57:33 +03:00
|
|
|
ordByExpML <- withArgM args "order_by" parseOrderBy
|
|
|
|
let ordByExpM = NE.nonEmpty =<< ordByExpML
|
2018-10-05 11:56:47 +03:00
|
|
|
limitExpM <- withArgM args "limit" parseLimit
|
2019-09-14 09:01:06 +03:00
|
|
|
offsetExpM <- withArgM args "offset" $ asPGColumnValue >=> openOpaqueValue >=> txtConverter
|
2019-09-19 07:47:36 +03:00
|
|
|
distOnColsML <- withArgM args "distinct_on" $ parseColumns colGNameMap
|
2018-11-23 04:53:56 +03:00
|
|
|
let distOnColsM = NE.nonEmpty =<< distOnColsML
|
|
|
|
mapM_ (validateDistOn ordByExpM) distOnColsM
|
|
|
|
return $ RS.TableArgs whereExpM ordByExpM limitExpM offsetExpM distOnColsM
|
|
|
|
where
|
|
|
|
validateDistOn Nothing _ = return ()
|
|
|
|
validateDistOn (Just ordBys) cols = withPathK "args" $ do
|
|
|
|
let colsLen = length cols
|
|
|
|
initOrdBys = take colsLen $ toList ordBys
|
|
|
|
initOrdByCols = flip mapMaybe initOrdBys $ \ob ->
|
|
|
|
case obiColumn ob of
|
2020-02-13 20:38:23 +03:00
|
|
|
RS.AOCPG pgCol -> Just pgCol
|
|
|
|
_ -> Nothing
|
2018-11-23 04:53:56 +03:00
|
|
|
isValid = (colsLen == length initOrdByCols)
|
|
|
|
&& all (`elem` initOrdByCols) (toList cols)
|
|
|
|
|
|
|
|
unless isValid $ throwVE
|
|
|
|
"\"distinct_on\" columns must match initial \"order_by\" columns"
|
2018-10-05 11:56:47 +03:00
|
|
|
|
2019-04-17 12:48:41 +03:00
|
|
|
type AnnSimpleSelect = RS.AnnSimpleSelG UnresolvedVal
|
|
|
|
|
2018-10-05 11:56:47 +03:00
|
|
|
fromField
|
2019-10-16 17:33:34 +03:00
|
|
|
:: ( MonadReusability m, MonadError QErr m, MonadReader r m, Has FieldMap r
|
2019-03-01 14:45:04 +03:00
|
|
|
, Has OrdByCtx r, Has SQLGenCtx r
|
|
|
|
)
|
2019-10-18 11:29:47 +03:00
|
|
|
=> RS.SelectFromG UnresolvedVal
|
2019-09-19 07:47:36 +03:00
|
|
|
-> PGColGNameMap
|
|
|
|
-> AnnBoolExpPartialSQL
|
|
|
|
-> Maybe Int
|
|
|
|
-> Field -> m AnnSimpleSelect
|
2019-10-18 11:29:47 +03:00
|
|
|
fromField selFrom colGNameMap permFilter permLimitM fld = fieldAsPath fld $ do
|
2019-09-19 07:47:36 +03:00
|
|
|
tableArgs <- parseTableArgs colGNameMap args
|
2020-02-13 20:38:23 +03:00
|
|
|
annFlds <- processTableSelectionSet (_fType fld) $ _fSelSet fld
|
2019-04-17 12:48:41 +03:00
|
|
|
let unresolvedPermFltr = fmapAnnBoolExp partialSQLExpToUnresolvedVal permFilter
|
2019-10-18 11:29:47 +03:00
|
|
|
let tabPerm = RS.TablePerm unresolvedPermFltr permLimitM
|
2019-03-01 14:45:04 +03:00
|
|
|
strfyNum <- stringifyNum <$> asks getter
|
2019-10-18 11:29:47 +03:00
|
|
|
return $ RS.AnnSelG annFlds selFrom tabPerm tableArgs strfyNum
|
2018-06-27 16:11:32 +03:00
|
|
|
where
|
|
|
|
args = _fArguments fld
|
|
|
|
|
2018-10-26 14:57:33 +03:00
|
|
|
getOrdByItemMap
|
2018-06-27 16:11:32 +03:00
|
|
|
:: ( MonadError QErr m
|
|
|
|
, MonadReader r m
|
2018-10-26 14:57:33 +03:00
|
|
|
, Has OrdByCtx r
|
2018-06-27 16:11:32 +03:00
|
|
|
)
|
2018-10-26 14:57:33 +03:00
|
|
|
=> G.NamedType -> m OrdByItemMap
|
|
|
|
getOrdByItemMap nt = do
|
2018-06-27 16:11:32 +03:00
|
|
|
ordByCtx <- asks getter
|
2018-10-26 14:57:33 +03:00
|
|
|
onNothing (Map.lookup nt ordByCtx) $
|
|
|
|
throw500 $ "could not lookup " <> showNamedTy nt
|
2018-06-27 16:11:32 +03:00
|
|
|
|
|
|
|
parseOrderBy
|
2019-10-16 17:33:34 +03:00
|
|
|
:: ( MonadReusability m
|
|
|
|
, MonadError QErr m
|
2018-06-27 16:11:32 +03:00
|
|
|
, MonadReader r m
|
2018-10-26 14:57:33 +03:00
|
|
|
, Has OrdByCtx r
|
2018-06-27 16:11:32 +03:00
|
|
|
)
|
2019-04-17 12:48:41 +03:00
|
|
|
=> AnnInpVal -> m [RS.AnnOrderByItemG UnresolvedVal]
|
2018-10-26 14:57:33 +03:00
|
|
|
parseOrderBy = fmap concat . withArray f
|
|
|
|
where
|
|
|
|
f _ = mapM (withObject (getAnnObItems id))
|
|
|
|
|
|
|
|
getAnnObItems
|
2019-10-16 17:33:34 +03:00
|
|
|
:: ( MonadReusability m
|
|
|
|
, MonadError QErr m
|
2018-10-26 14:57:33 +03:00
|
|
|
, MonadReader r m
|
|
|
|
, Has OrdByCtx r
|
|
|
|
)
|
2019-04-17 12:48:41 +03:00
|
|
|
=> (RS.AnnObColG UnresolvedVal -> RS.AnnObColG UnresolvedVal)
|
2018-10-26 14:57:33 +03:00
|
|
|
-> G.NamedType
|
|
|
|
-> AnnGObject
|
2019-04-17 12:48:41 +03:00
|
|
|
-> m [RS.AnnOrderByItemG UnresolvedVal]
|
2018-10-26 14:57:33 +03:00
|
|
|
getAnnObItems f nt obj = do
|
|
|
|
ordByItemMap <- getOrdByItemMap nt
|
|
|
|
fmap concat $ forM (OMap.toList obj) $ \(k, v) -> do
|
|
|
|
ordByItem <- onNothing (Map.lookup k ordByItemMap) $ throw500 $
|
|
|
|
"cannot lookup " <> showName k <> " order by item in "
|
|
|
|
<> showNamedTy nt <> " map"
|
|
|
|
case ordByItem of
|
|
|
|
OBIPGCol ci -> do
|
2020-02-13 20:38:23 +03:00
|
|
|
let aobCol = f $ RS.AOCPG $ pgiColumn ci
|
2019-08-22 11:14:27 +03:00
|
|
|
(_, enumValM) <- asEnumValM v
|
|
|
|
ordByItemM <- forM enumValM $ \enumVal -> do
|
|
|
|
(ordTy, nullsOrd) <- parseOrderByEnum enumVal
|
|
|
|
return $ mkOrdByItemG ordTy aobCol nullsOrd
|
|
|
|
return $ maybe [] pure ordByItemM
|
|
|
|
|
2018-10-26 14:57:33 +03:00
|
|
|
OBIRel ri fltr -> do
|
2019-04-17 12:48:41 +03:00
|
|
|
let unresolvedFltr = fmapAnnBoolExp partialSQLExpToUnresolvedVal fltr
|
|
|
|
let annObColFn = f . RS.AOCObj ri unresolvedFltr
|
2019-08-22 11:14:27 +03:00
|
|
|
flip withObjectM v $ \nameTy objM ->
|
|
|
|
maybe (pure []) (getAnnObItems annObColFn nameTy) objM
|
2018-10-26 14:57:33 +03:00
|
|
|
|
2019-09-19 07:47:36 +03:00
|
|
|
OBIAgg ri relColGNameMap fltr -> do
|
2019-04-17 12:48:41 +03:00
|
|
|
let unresolvedFltr = fmapAnnBoolExp partialSQLExpToUnresolvedVal fltr
|
|
|
|
let aobColFn = f . RS.AOCAgg ri unresolvedFltr
|
2019-08-22 11:14:27 +03:00
|
|
|
flip withObjectM v $ \_ objM ->
|
2019-09-19 07:47:36 +03:00
|
|
|
maybe (pure []) (parseAggOrdBy relColGNameMap aobColFn) objM
|
2018-12-12 15:58:39 +03:00
|
|
|
|
2018-12-13 10:26:15 +03:00
|
|
|
mkOrdByItemG :: S.OrderType -> a -> S.NullsOrder -> OrderByItemG a
|
|
|
|
mkOrdByItemG ordTy aobCol nullsOrd =
|
|
|
|
OrderByItemG (Just $ OrderType ordTy) aobCol (Just $ NullsOrder nullsOrd)
|
|
|
|
|
2018-12-12 15:58:39 +03:00
|
|
|
parseAggOrdBy
|
2019-10-16 17:33:34 +03:00
|
|
|
:: (MonadReusability m, MonadError QErr m)
|
2019-09-19 07:47:36 +03:00
|
|
|
=> PGColGNameMap
|
|
|
|
-> (RS.AnnAggOrdBy -> RS.AnnObColG UnresolvedVal)
|
2018-12-12 15:58:39 +03:00
|
|
|
-> AnnGObject
|
2019-04-17 12:48:41 +03:00
|
|
|
-> m [RS.AnnOrderByItemG UnresolvedVal]
|
2019-09-19 07:47:36 +03:00
|
|
|
parseAggOrdBy colGNameMap f annObj =
|
2018-12-12 15:58:39 +03:00
|
|
|
fmap concat <$> forM (OMap.toList annObj) $ \(op, obVal) ->
|
|
|
|
case op of
|
|
|
|
"count" -> do
|
2019-08-22 11:14:27 +03:00
|
|
|
(_, enumValM) <- asEnumValM obVal
|
|
|
|
ordByItemM <- forM enumValM $ \enumVal -> do
|
|
|
|
(ordTy, nullsOrd) <- parseOrderByEnum enumVal
|
|
|
|
return $ mkOrdByItemG ordTy (f RS.AAOCount) nullsOrd
|
|
|
|
return $ maybe [] pure ordByItemM
|
2018-12-12 15:58:39 +03:00
|
|
|
|
|
|
|
G.Name opT ->
|
2019-08-22 11:14:27 +03:00
|
|
|
flip withObject obVal $ \_ opObObj -> fmap catMaybes $
|
2019-09-19 07:47:36 +03:00
|
|
|
forM (OMap.toList opObObj) $ \(colName, eVal) -> do
|
2019-08-22 11:14:27 +03:00
|
|
|
(_, enumValM) <- asEnumValM eVal
|
|
|
|
forM enumValM $ \enumVal -> do
|
|
|
|
(ordTy, nullsOrd) <- parseOrderByEnum enumVal
|
2019-09-19 07:47:36 +03:00
|
|
|
col <- pgiColumn <$> resolvePGCol colGNameMap colName
|
|
|
|
let aobCol = f $ RS.AAOOp opT col
|
2019-08-22 11:14:27 +03:00
|
|
|
return $ mkOrdByItemG ordTy aobCol nullsOrd
|
2018-12-12 15:58:39 +03:00
|
|
|
|
2018-10-26 14:57:33 +03:00
|
|
|
parseOrderByEnum
|
|
|
|
:: (MonadError QErr m)
|
|
|
|
=> G.EnumValue
|
|
|
|
-> m (S.OrderType, S.NullsOrder)
|
|
|
|
parseOrderByEnum = \case
|
|
|
|
G.EnumValue "asc" -> return (S.OTAsc, S.NLast)
|
2018-11-22 07:58:18 +03:00
|
|
|
G.EnumValue "asc_nulls_last" -> return (S.OTAsc, S.NLast)
|
2018-10-26 14:57:33 +03:00
|
|
|
G.EnumValue "asc_nulls_first" -> return (S.OTAsc, S.NFirst)
|
2018-11-22 07:58:18 +03:00
|
|
|
G.EnumValue "desc" -> return (S.OTDesc, S.NFirst)
|
2018-10-26 14:57:33 +03:00
|
|
|
G.EnumValue "desc_nulls_first" -> return (S.OTDesc, S.NFirst)
|
2018-11-22 07:58:18 +03:00
|
|
|
G.EnumValue "desc_nulls_last" -> return (S.OTDesc, S.NLast)
|
2018-10-26 14:57:33 +03:00
|
|
|
G.EnumValue v -> throw500 $
|
|
|
|
"enum value " <> showName v <> " not found in type order_by"
|
2018-06-27 16:11:32 +03:00
|
|
|
|
2019-10-16 17:33:34 +03:00
|
|
|
parseLimit :: (MonadReusability m, MonadError QErr m) => AnnInpVal -> m Int
|
2018-08-06 15:15:08 +03:00
|
|
|
parseLimit v = do
|
2019-09-14 09:01:06 +03:00
|
|
|
pgColVal <- openOpaqueValue =<< asPGColumnValue v
|
|
|
|
limit <- maybe noIntErr return . pgColValueToInt . pstValue $ _apvValue pgColVal
|
2018-08-06 15:15:08 +03:00
|
|
|
-- validate int value
|
|
|
|
onlyPositiveInt limit
|
|
|
|
return limit
|
|
|
|
where
|
2018-12-04 16:37:38 +03:00
|
|
|
noIntErr = throwVE "expecting Integer value for \"limit\""
|
2018-08-06 15:15:08 +03:00
|
|
|
|
2019-04-17 12:48:41 +03:00
|
|
|
type AnnSimpleSel = RS.AnnSimpleSelG UnresolvedVal
|
|
|
|
|
2018-10-05 11:56:47 +03:00
|
|
|
fromFieldByPKey
|
2019-10-16 17:33:34 +03:00
|
|
|
:: ( MonadReusability m
|
|
|
|
, MonadError QErr m
|
2019-02-22 13:27:38 +03:00
|
|
|
, MonadReader r m
|
|
|
|
, Has FieldMap r
|
|
|
|
, Has OrdByCtx r
|
2019-03-01 14:45:04 +03:00
|
|
|
, Has SQLGenCtx r
|
2019-02-22 13:27:38 +03:00
|
|
|
)
|
2019-04-17 12:48:41 +03:00
|
|
|
=> QualifiedTable -> PGColArgMap
|
|
|
|
-> AnnBoolExpPartialSQL -> Field -> m AnnSimpleSel
|
|
|
|
fromFieldByPKey tn colArgMap permFilter fld = fieldAsPath fld $ do
|
|
|
|
boolExp <- pgColValToBoolExp colArgMap $ _fArguments fld
|
2020-02-13 20:38:23 +03:00
|
|
|
annFlds <- processTableSelectionSet fldTy $ _fSelSet fld
|
2019-10-18 11:29:47 +03:00
|
|
|
let tabFrom = RS.FromTable tn
|
2019-04-17 12:48:41 +03:00
|
|
|
unresolvedPermFltr = fmapAnnBoolExp partialSQLExpToUnresolvedVal
|
|
|
|
permFilter
|
|
|
|
tabPerm = RS.TablePerm unresolvedPermFltr Nothing
|
2019-03-01 14:45:04 +03:00
|
|
|
tabArgs = RS.noTableArgs { RS._taWhere = Just boolExp}
|
|
|
|
strfyNum <- stringifyNum <$> asks getter
|
|
|
|
return $ RS.AnnSelG annFlds tabFrom tabPerm tabArgs strfyNum
|
2019-02-22 13:27:38 +03:00
|
|
|
where
|
|
|
|
fldTy = _fType fld
|
2018-10-05 11:56:47 +03:00
|
|
|
|
2018-06-27 16:11:32 +03:00
|
|
|
convertSelect
|
2019-10-16 17:33:34 +03:00
|
|
|
:: ( MonadReusability m, MonadError QErr m, MonadReader r m, Has FieldMap r
|
2019-04-17 12:48:41 +03:00
|
|
|
, Has OrdByCtx r, Has SQLGenCtx r
|
|
|
|
)
|
2020-02-13 20:38:23 +03:00
|
|
|
=> SelOpCtx -> Field -> m (RS.AnnSimpleSelG UnresolvedVal)
|
2019-04-17 12:48:41 +03:00
|
|
|
convertSelect opCtx fld =
|
2020-02-13 20:38:23 +03:00
|
|
|
withPathK "selectionSet" $
|
2019-10-18 11:29:47 +03:00
|
|
|
fromField (RS.FromTable qt) colGNameMap permFilter permLimit fld
|
2019-02-22 13:27:38 +03:00
|
|
|
where
|
2019-09-19 07:47:36 +03:00
|
|
|
SelOpCtx qt _ colGNameMap permFilter permLimit = opCtx
|
2018-08-27 17:17:03 +03:00
|
|
|
|
|
|
|
convertSelectByPKey
|
2019-10-16 17:33:34 +03:00
|
|
|
:: ( MonadReusability m, MonadError QErr m, MonadReader r m, Has FieldMap r
|
2019-04-17 12:48:41 +03:00
|
|
|
, Has OrdByCtx r, Has SQLGenCtx r
|
|
|
|
)
|
2020-02-13 20:38:23 +03:00
|
|
|
=> SelPkOpCtx -> Field -> m (RS.AnnSimpleSelG UnresolvedVal)
|
2019-04-17 12:48:41 +03:00
|
|
|
convertSelectByPKey opCtx fld =
|
2020-02-13 20:38:23 +03:00
|
|
|
withPathK "selectionSet" $
|
2019-04-17 12:48:41 +03:00
|
|
|
fromFieldByPKey qt colArgMap permFilter fld
|
2019-02-22 13:27:38 +03:00
|
|
|
where
|
|
|
|
SelPkOpCtx qt _ permFilter colArgMap = opCtx
|
2018-10-26 12:02:44 +03:00
|
|
|
|
|
|
|
-- agg select related
|
2019-10-16 17:33:34 +03:00
|
|
|
parseColumns :: (MonadReusability m, MonadError QErr m) => PGColGNameMap -> AnnInpVal -> m [PGCol]
|
2019-09-19 07:47:36 +03:00
|
|
|
parseColumns allColFldMap val =
|
2018-11-14 15:59:59 +03:00
|
|
|
flip withArray val $ \_ vals ->
|
|
|
|
forM vals $ \v -> do
|
2019-09-19 07:47:36 +03:00
|
|
|
(_, G.EnumValue enumVal) <- asEnumVal v
|
|
|
|
pgiColumn <$> resolvePGCol allColFldMap enumVal
|
2018-11-14 15:59:59 +03:00
|
|
|
|
2019-10-16 17:33:34 +03:00
|
|
|
convertCount :: (MonadReusability m, MonadError QErr m) => PGColGNameMap -> ArgsMap -> m S.CountType
|
2019-09-19 07:47:36 +03:00
|
|
|
convertCount colGNameMap args = do
|
|
|
|
columnsM <- withArgM args "columns" $ parseColumns colGNameMap
|
2018-11-14 15:59:59 +03:00
|
|
|
isDistinct <- or <$> withArgM args "distinct" parseDistinct
|
|
|
|
maybe (return S.CTStar) (mkCType isDistinct) columnsM
|
|
|
|
where
|
|
|
|
parseDistinct v = do
|
2019-09-14 09:01:06 +03:00
|
|
|
val <- openOpaqueValue =<< asPGColumnValue v
|
|
|
|
case pstValue $ _apvValue val of
|
2018-11-14 15:59:59 +03:00
|
|
|
PGValBoolean b -> return b
|
|
|
|
_ ->
|
|
|
|
throw500 "expecting Boolean for \"distinct\""
|
|
|
|
|
|
|
|
mkCType isDistinct cols = return $
|
|
|
|
bool (S.CTSimple cols) (S.CTDistinct cols) isDistinct
|
|
|
|
|
2019-01-25 06:31:54 +03:00
|
|
|
toFields :: [(T.Text, a)] -> RS.Fields a
|
2018-12-12 15:58:39 +03:00
|
|
|
toFields = map (first FieldName)
|
|
|
|
|
2018-10-26 12:02:44 +03:00
|
|
|
convertColFlds
|
2019-10-16 17:33:34 +03:00
|
|
|
:: (MonadError QErr m)
|
2019-09-19 07:47:36 +03:00
|
|
|
=> PGColGNameMap -> G.NamedType -> SelSet -> m RS.ColFlds
|
|
|
|
convertColFlds colGNameMap ty selSet = fmap toFields $
|
2018-10-26 12:02:44 +03:00
|
|
|
withSelSet selSet $ \fld ->
|
|
|
|
case _fName fld of
|
|
|
|
"__typename" -> return $ RS.PCFExp $ G.unName $ G.unNamedType ty
|
2019-09-19 07:47:36 +03:00
|
|
|
n -> (RS.PCFCol . pgiColumn) <$> resolvePGCol colGNameMap n
|
2018-10-26 12:02:44 +03:00
|
|
|
|
2019-09-19 07:47:36 +03:00
|
|
|
convertAggFld
|
2019-10-16 17:33:34 +03:00
|
|
|
:: (MonadReusability m, MonadError QErr m)
|
2019-09-19 07:47:36 +03:00
|
|
|
=> PGColGNameMap -> G.NamedType -> SelSet -> m RS.AggFlds
|
|
|
|
convertAggFld colGNameMap ty selSet = fmap toFields $
|
2018-10-26 12:02:44 +03:00
|
|
|
withSelSet selSet $ \fld -> do
|
|
|
|
let fType = _fType fld
|
|
|
|
fSelSet = _fSelSet fld
|
|
|
|
case _fName fld of
|
|
|
|
"__typename" -> return $ RS.AFExp $ G.unName $ G.unNamedType ty
|
2019-09-19 07:47:36 +03:00
|
|
|
"count" -> RS.AFCount <$> convertCount colGNameMap (_fArguments fld)
|
2018-11-14 15:59:59 +03:00
|
|
|
n -> do
|
2019-09-19 07:47:36 +03:00
|
|
|
colFlds <- convertColFlds colGNameMap fType fSelSet
|
2018-11-14 15:59:59 +03:00
|
|
|
unless (isAggFld n) $ throwInvalidFld n
|
|
|
|
return $ RS.AFOp $ RS.AggOp (G.unName n) colFlds
|
|
|
|
where
|
|
|
|
throwInvalidFld (G.Name t) =
|
|
|
|
throw500 $ "unexpected field in _aggregate node: " <> t
|
2018-10-26 12:02:44 +03:00
|
|
|
|
2019-04-17 12:48:41 +03:00
|
|
|
type AnnAggSel = RS.AnnAggSelG UnresolvedVal
|
|
|
|
|
2018-10-26 12:02:44 +03:00
|
|
|
fromAggField
|
2019-10-16 17:33:34 +03:00
|
|
|
:: ( MonadReusability m, MonadError QErr m, MonadReader r m, Has FieldMap r
|
2019-03-01 14:45:04 +03:00
|
|
|
, Has OrdByCtx r, Has SQLGenCtx r
|
|
|
|
)
|
2019-12-10 05:27:44 +03:00
|
|
|
=> RS.SelectFromG UnresolvedVal
|
2019-09-19 07:47:36 +03:00
|
|
|
-> PGColGNameMap
|
|
|
|
-> AnnBoolExpPartialSQL
|
|
|
|
-> Maybe Int
|
|
|
|
-> Field -> m AnnAggSel
|
2019-12-10 05:27:44 +03:00
|
|
|
fromAggField selectFrom colGNameMap permFilter permLimit fld = fieldAsPath fld $ do
|
2019-09-19 07:47:36 +03:00
|
|
|
tableArgs <- parseTableArgs colGNameMap args
|
|
|
|
aggSelFlds <- fromAggSelSet colGNameMap (_fType fld) (_fSelSet fld)
|
2019-04-17 12:48:41 +03:00
|
|
|
let unresolvedPermFltr =
|
|
|
|
fmapAnnBoolExp partialSQLExpToUnresolvedVal permFilter
|
2019-12-10 05:27:44 +03:00
|
|
|
let tabPerm = RS.TablePerm unresolvedPermFltr permLimit
|
2019-03-01 14:45:04 +03:00
|
|
|
strfyNum <- stringifyNum <$> asks getter
|
2019-12-10 05:27:44 +03:00
|
|
|
return $ RS.AnnSelG aggSelFlds selectFrom tabPerm tableArgs strfyNum
|
2018-10-26 12:02:44 +03:00
|
|
|
where
|
|
|
|
args = _fArguments fld
|
|
|
|
|
2019-04-17 12:48:41 +03:00
|
|
|
convertAggSelect
|
2019-10-16 17:33:34 +03:00
|
|
|
:: ( MonadReusability m, MonadError QErr m, MonadReader r m, Has FieldMap r
|
2019-04-17 12:48:41 +03:00
|
|
|
, Has OrdByCtx r, Has SQLGenCtx r
|
|
|
|
)
|
2020-02-13 20:38:23 +03:00
|
|
|
=> SelOpCtx -> Field -> m (RS.AnnAggSelG UnresolvedVal)
|
2019-04-17 12:48:41 +03:00
|
|
|
convertAggSelect opCtx fld =
|
2020-02-13 20:38:23 +03:00
|
|
|
withPathK "selectionSet" $
|
2019-12-10 05:27:44 +03:00
|
|
|
fromAggField (RS.FromTable qt) colGNameMap permFilter permLimit fld
|
2019-02-22 13:27:38 +03:00
|
|
|
where
|
2019-09-19 07:47:36 +03:00
|
|
|
SelOpCtx qt _ colGNameMap permFilter permLimit = opCtx
|
2019-01-25 06:31:54 +03:00
|
|
|
|
|
|
|
parseFunctionArgs
|
2019-10-16 17:33:34 +03:00
|
|
|
:: (MonadReusability m, MonadError QErr m)
|
2019-11-20 09:47:06 +03:00
|
|
|
=> Seq.Seq a
|
|
|
|
-> (a -> InputFunctionArgument)
|
2019-12-27 01:32:48 +03:00
|
|
|
-> Maybe AnnInpVal
|
2019-08-28 22:27:15 +03:00
|
|
|
-> m (RS.FunctionArgsExpG UnresolvedVal)
|
2019-12-27 01:32:48 +03:00
|
|
|
parseFunctionArgs argSeq argFn = withPathK "args" . \case
|
|
|
|
Nothing -> do
|
|
|
|
-- The input "args" field is not provided, hence resolve only known
|
|
|
|
-- input arguments as positional arguments
|
|
|
|
let positionalArgs = mapMaybe ((^? _IFAKnown._2) . argFn) $ toList argSeq
|
|
|
|
pure RS.emptyFunctionArgsExp{RS._faePositional = positionalArgs}
|
|
|
|
|
|
|
|
Just val -> flip withObject val $ \_ obj -> do
|
|
|
|
(positionalArgs, argsLeft) <- spanMaybeM (parsePositionalArg obj) argSeq
|
|
|
|
namedArgs <- Map.fromList . catMaybes <$> traverse (parseNamedArg obj) argsLeft
|
|
|
|
pure $ RS.FunctionArgsExp positionalArgs namedArgs
|
2019-06-04 15:43:28 +03:00
|
|
|
where
|
2019-11-20 09:47:06 +03:00
|
|
|
parsePositionalArg obj inputArg = case argFn inputArg of
|
|
|
|
IFAKnown _ resolvedVal -> pure $ Just resolvedVal
|
|
|
|
IFAUnknown (FunctionArgItem gqlName _ _) ->
|
|
|
|
maybe (pure Nothing) (fmap Just . parseArg) $ OMap.lookup gqlName obj
|
2019-08-28 22:27:15 +03:00
|
|
|
|
2019-09-14 09:01:06 +03:00
|
|
|
parseArg = fmap (maybe (UVSQL S.SENull) mkParameterizablePGValue) . asPGColumnValueM
|
2019-08-28 22:27:15 +03:00
|
|
|
|
2019-11-20 09:47:06 +03:00
|
|
|
parseNamedArg obj inputArg = case argFn inputArg of
|
|
|
|
IFAKnown argName resolvedVal ->
|
|
|
|
pure $ Just (getFuncArgNameTxt argName, resolvedVal)
|
|
|
|
IFAUnknown (FunctionArgItem gqlName maybeSqlName hasDefault) ->
|
|
|
|
case OMap.lookup gqlName obj of
|
|
|
|
Just argInpVal -> case maybeSqlName of
|
|
|
|
Just sqlName -> Just . (getFuncArgNameTxt sqlName,) <$> parseArg argInpVal
|
|
|
|
Nothing -> throw400 NotSupported
|
|
|
|
"Only last set of positional arguments can be omitted"
|
|
|
|
Nothing -> if not (unHasDefault hasDefault) then
|
|
|
|
throw400 NotSupported "Non default arguments cannot be omitted"
|
|
|
|
else pure Nothing
|
2019-04-17 12:48:41 +03:00
|
|
|
|
2019-12-10 05:27:44 +03:00
|
|
|
makeFunctionSelectFrom
|
2019-10-16 17:33:34 +03:00
|
|
|
:: (MonadReusability m, MonadError QErr m)
|
2019-12-10 05:27:44 +03:00
|
|
|
=> QualifiedFunction
|
2019-11-20 09:47:06 +03:00
|
|
|
-> FunctionArgSeq
|
2019-04-17 12:48:41 +03:00
|
|
|
-> Field
|
2019-12-10 05:27:44 +03:00
|
|
|
-> m (RS.SelectFromG UnresolvedVal)
|
2019-12-27 01:32:48 +03:00
|
|
|
makeFunctionSelectFrom qf argSeq fld = withPathK "args" $ do
|
|
|
|
funcArgs <- parseFunctionArgs argSeq argFn $ Map.lookup "args" $ _fArguments fld
|
2020-02-13 20:38:23 +03:00
|
|
|
pure $ RS.FromFunction qf (RS.AEInput <$> funcArgs) Nothing
|
2019-11-20 09:47:06 +03:00
|
|
|
where
|
|
|
|
argFn (IAUserProvided val) = IFAUnknown val
|
|
|
|
argFn (IASessionVariables argName) = IFAKnown argName UVSession
|
2019-04-17 12:48:41 +03:00
|
|
|
|
|
|
|
convertFuncQuerySimple
|
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
|
|
|
|
, Has OrdByCtx r
|
|
|
|
, Has SQLGenCtx r
|
|
|
|
)
|
2020-02-13 20:38:23 +03:00
|
|
|
=> FuncQOpCtx -> Field -> m AnnSimpleSelect
|
2019-04-17 12:48:41 +03:00
|
|
|
convertFuncQuerySimple funcOpCtx fld =
|
2019-12-10 05:27:44 +03:00
|
|
|
withPathK "selectionSet" $ fieldAsPath fld $ do
|
|
|
|
selectFrom <- makeFunctionSelectFrom qf argSeq fld
|
2020-02-13 20:38:23 +03:00
|
|
|
fromField selectFrom colGNameMap permFilter permLimit fld
|
2019-02-22 13:27:38 +03:00
|
|
|
where
|
2019-12-10 05:27:44 +03:00
|
|
|
FuncQOpCtx qf argSeq _ colGNameMap permFilter permLimit = funcOpCtx
|
2019-04-17 12:48:41 +03:00
|
|
|
|
|
|
|
convertFuncQueryAgg
|
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
|
|
|
|
, Has OrdByCtx r
|
|
|
|
, Has SQLGenCtx r
|
|
|
|
)
|
2020-02-13 20:38:23 +03:00
|
|
|
=> FuncQOpCtx -> Field -> m AnnAggSel
|
2019-04-17 12:48:41 +03:00
|
|
|
convertFuncQueryAgg funcOpCtx fld =
|
2019-12-10 05:27:44 +03:00
|
|
|
withPathK "selectionSet" $ fieldAsPath fld $ do
|
|
|
|
selectFrom <- makeFunctionSelectFrom qf argSeq fld
|
2020-02-13 20:38:23 +03:00
|
|
|
fromAggField selectFrom colGNameMap permFilter permLimit fld
|
2019-04-17 12:48:41 +03:00
|
|
|
where
|
2019-12-10 05:27:44 +03:00
|
|
|
FuncQOpCtx qf argSeq _ colGNameMap permFilter permLimit = funcOpCtx
|