Skip to content

Commit

Permalink
Add just_check field to glean UserQueryOptions
Browse files Browse the repository at this point in the history
Summary:
Add a just_check option to UserQueryOption, to allow a result to be returned after compilation (without actually query the db), so we can syntax-check a query.

**Next steps** will add to daiquery UI, so we can get syntax error highlighting in the editor while the query is written

Reviewed By: malanka

Differential Revision: D64957730

fbshipit-source-id: 5611d29113340860ccbc0fca53707479e1950081
  • Loading branch information
Julia Molin authored and facebook-github-bot committed Oct 31, 2024
1 parent b764242 commit 52c79d3
Show file tree
Hide file tree
Showing 4 changed files with 107 additions and 10 deletions.
90 changes: 80 additions & 10 deletions glean/db/Glean/Query/UserQuery.hs
Original file line number Diff line number Diff line change
Expand Up @@ -93,6 +93,7 @@ import Glean.Schema.Util
import Glean.Util.Observed as Observed
import Glean.Query.Typecheck
import Glean.Bytecode.SysCalls (userQuerySysCalls)
import Glean.Types (UserQueryCont)

-- NOTE: We keep the public interface monomorphic, at least for now.

Expand Down Expand Up @@ -599,7 +600,6 @@ userQueryWrites env odb config bounds lookup repo pred q = do
minus = Map.unionWith (-)
hasFacts pid m = maybe False (> 0) $ Map.lookup pid m


userQueryImpl
:: Database.Env
-> OpenDB s
Expand All @@ -619,7 +619,7 @@ userQueryImpl
bounds
lookup
repo
Thrift.UserQuery{..} = do
query@Thrift.UserQuery{..} = do
let opts = fromMaybe def userQuery_options

case Thrift.userQueryOptions_syntax opts of
Expand All @@ -628,22 +628,25 @@ userQueryImpl
"query syntax not supported: " <> Text.pack (show other)

let
schema@DbSchema{..} = odbSchema odb
opts = fromMaybe def userQuery_options
schema = odbSchema odb
stored = Thrift.userQueryOptions_store_derived_facts opts
debug = Thrift.userQueryOptions_debug opts

schemaVersion <-
schemaVersionForQuery schema config userQuery_schema_id
trans <- transformationsForQuery schema schemaVersion

(returnType, compileTime, irDiag, cont) <-
compileInfo <-
case Thrift.userQueryOptions_continuation opts of
Just ucont
| Just retTy <- Thrift.userQueryCont_returnType ucont -> do
(compileTime, _, returnType) <-
timeIt $ compileType schema schemaVersion retTy
return (returnType, compileTime, [], Right ucont)
return CompileInfo {
returnType = returnType,
compileTime = compileTime,
irDiag = [],
cont = Right ucont
}

-- This is either a new query or the continuation of a query
-- that returns a temporary predicate.
Expand All @@ -666,10 +669,55 @@ userQueryImpl
Just c -> Right c
Nothing -> Left query

return (ty, compileTime, irDiag, cont)
return CompileInfo {
returnType = ty,
compileTime = compileTime,
irDiag = irDiag,
cont = cont
}

if Thrift.userQueryOptions_just_check opts then do
return emptyResult
else do
runQuery env odb config bounds lookup repo compileInfo query

data CompileInfo = CompileInfo {
returnType :: Type,
compileTime :: Double,
irDiag :: [Text],
cont :: Either CodegenQuery UserQueryCont
}

runQuery
:: Database.Env
-> OpenDB s
-> ServerConfig.Config
-> Boundaries
-> Lookup
-> Thrift.Repo
-> CompileInfo
-> Thrift.UserQuery
-> IO (Results Stats Thrift.Fact)
runQuery
env
odb
config
bounds
lookup
repo
CompileInfo{..}
Thrift.UserQuery{..} = do
vlog 2 $ "return type: " <> show (displayDefault returnType)

let
schema@DbSchema{..} = odbSchema odb
opts = fromMaybe def userQuery_options
stored = Thrift.userQueryOptions_store_derived_facts opts

schemaVersion <-
schemaVersionForQuery schema config userQuery_schema_id
trans <- transformationsForQuery schema schemaVersion

details@PredicateDetails{..} <- case returnType of
Angle.PredicateTy (PidRef pid _) ->
case IntMap.lookup (fromIntegral (fromPid pid)) predicatesByPid of
Expand Down Expand Up @@ -745,6 +793,7 @@ userQueryImpl

Left query -> do
let
debug = Thrift.userQueryOptions_debug opts
bytecodeDiag sub =
[ "bytecode:\n" <> Text.unlines
(disassemble "Query" userQuerySysCalls $ compiledQuerySub sub)
Expand Down Expand Up @@ -802,8 +851,8 @@ userQueryImpl
}

return $ if Thrift.userQueryOptions_omit_results opts
then withoutFacts results
else results
then withoutFacts results
else results

transformationsForQuery
:: DbSchema
Expand Down Expand Up @@ -943,6 +992,27 @@ mkQueryRuntimeOptions
| otherwise -> ResultsOnly
}

emptyResult :: Results Stats fact
emptyResult = Results {
resFacts = mempty
, resPredicate = Nothing
, resNestedFacts = mempty
, resCont = Nothing
, resStats = Stats {
statFactCount = 0
, statResultCount = 0
, statFullScans = []
}
, resDiags = []
, resWriteHandle = Nothing
, resFactsSearched = Nothing
, resType = Nothing
, resBytecodeSize = Nothing
, resCompileTime = Nothing
, resCodegenTime = Nothing
, resExecutionTime = Nothing
}


{- Note [Writing derived facts]
Expand Down
7 changes: 7 additions & 0 deletions glean/hs/Glean/Query/Thrift/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,7 @@ module Glean.Query.Thrift.Internal
, showUserQueryStats
, displayQuery
, decodeResults
, justCheck
) where

import Control.Exception
Expand Down Expand Up @@ -215,6 +216,12 @@ store (Query q) = Query q'
q' = q { userQuery_options = Just (fromMaybe def (userQuery_options q))
{ userQueryOptions_store_derived_facts = True } }

justCheck :: Query a -> Query a
justCheck (Query q) = Query q'
where
q' = q { userQuery_options = Just (fromMaybe def (userQuery_options q))
{ userQueryOptions_just_check = True } }

reportUserQueryStats :: Thrift.UserQueryStats -> IO ()
reportUserQueryStats stats =
vlog 1 $ showUserQueryStats stats
Expand Down
3 changes: 3 additions & 0 deletions glean/if/glean.thrift
Original file line number Diff line number Diff line change
Expand Up @@ -510,6 +510,9 @@ struct UserQueryOptions {
// A more fine-grained alternative to recursive = true. Only
// fields of a predicate in the list will be fetched.
14: list<SourcePredicate> expand_predicates;

// if true, the query will be compiled, but no facts will be retrieved
15: bool just_check = false;
}

struct QueryDebugOptions {
Expand Down
17 changes: 17 additions & 0 deletions glean/test/tests/Angle/MiscTest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -46,6 +46,7 @@ main = withUnitTest $ testRunner $ TestList
, TestLabel "limitBytes" limitTest
, TestLabel "fullScans" fullScansTest
, TestLabel "newold" $ newOldTest id
, TestLabel "justCheck" justCheckTest
]

newOldTest :: (forall a . Query a -> Query a) -> Test
Expand Down Expand Up @@ -421,6 +422,22 @@ limitTest = dbTestCase $ \env repo -> do
Angle.query $ predicate @Glean.Test.Edge wild
assertBool "limitBytes" (length results == 2 && truncated)

justCheckTest :: Test
justCheckTest = dbTestCase $ \env repo -> do
results <- runQuery_ env repo $ justCheck $ Angle.query $
predicate @Cxx.Name wild
assertEqual "just check" 0 (length results)

results <- try $ runQuery_ env repo $ justCheck $ angleData @Text
[s|
Cxx1.Name X
|]
assertBool "just check - bad query" $
case results of
Left (BadQuery _) -> True
_ -> False


fullScansTest :: Test
fullScansTest = TestList $
[ TestLabel "no full scans" $ TestCase $ withTestDB [] $ \env repo -> do
Expand Down

0 comments on commit 52c79d3

Please sign in to comment.