graphql-engine/server/src-lib/Hasura/GraphQL/Schema/Common.hs
Brandon Simmons b167120f96 server: add explicit export lists in OSS server and enforce with warning
We'll see if this improves compile times at all, but I think it's worth
doing as at least the most minimal form of module documentation.

This was accomplished by first compiling everything with
-ddump-minimal-imports, and then a bunch of scripting (with help from
ormolu)

**EDIT** it doesn't seem to improve CI compile times but the noise floor is high as it looks like we're not caching library dependencies anymore

PR-URL: https://github.com/hasura/graphql-engine-mono/pull/2730
GitOrigin-RevId: 667eb8de1e0f1af70420cbec90402922b8b84cb4
2021-11-04 16:09:38 +00:00

183 lines
6.3 KiB
Haskell
Raw Blame History

This file contains ambiguous Unicode characters

This file contains Unicode characters that might be confused with other characters. If you think that this is intentional, you can safely ignore this warning. Use the Escape button to reveal them.

module Hasura.GraphQL.Schema.Common
( AggSelectExp,
AnnotatedField,
AnnotatedFields,
ConnectionFields,
ConnectionSelectExp,
EdgeFields,
QueryContext (QueryContext, qcDangerousBooleanCollapse, qcFunctionPermsContext, qcQueryType, qcRemoteRelationshipContext, qcStringifyNum),
RemoteRelationshipQueryContext (RemoteRelationshipQueryContext, _rrscParsedIntrospection),
SelectArgs,
SelectExp,
TablePerms,
comparisonAggOperators,
currentNodeIdVersion,
mapField,
mkDescriptionWith,
nodeIdVersionInt,
numericAggOperators,
optionalFieldParser,
parsedSelectionsToFields,
partialSQLExpToUnpreparedValue,
requiredFieldParser,
takeValidFunctions,
takeValidTables,
textToName,
)
where
import Data.Aeson qualified as J
import Data.Either (isRight)
import Data.HashMap.Strict qualified as Map
import Data.HashMap.Strict.InsOrd qualified as OMap
import Data.Text qualified as T
import Data.Text.Extended
import Hasura.Backends.Postgres.SQL.Types qualified as PG
import Hasura.Base.Error
import Hasura.GraphQL.Execute.Types qualified as ET (GraphQLQueryType)
import Hasura.GraphQL.Parser (UnpreparedValue)
import Hasura.GraphQL.Parser qualified as P
import Hasura.Prelude
import Hasura.RQL.IR.Select qualified as IR
import Hasura.RQL.Types
import Language.GraphQL.Draft.Syntax as G
type SelectExp b = IR.AnnSimpleSelectG b (IR.RemoteSelect UnpreparedValue) (UnpreparedValue b)
type AggSelectExp b = IR.AnnAggregateSelectG b (IR.RemoteSelect UnpreparedValue) (UnpreparedValue b)
type ConnectionSelectExp b = IR.ConnectionSelect b (IR.RemoteSelect UnpreparedValue) (UnpreparedValue b)
type SelectArgs b = IR.SelectArgsG b (UnpreparedValue b)
type TablePerms b = IR.TablePermG b (UnpreparedValue b)
type AnnotatedFields b = IR.AnnFieldsG b (IR.RemoteSelect UnpreparedValue) (UnpreparedValue b)
type AnnotatedField b = IR.AnnFieldG b (IR.RemoteSelect UnpreparedValue) (UnpreparedValue b)
type ConnectionFields b = IR.ConnectionFields b (IR.RemoteSelect UnpreparedValue) (UnpreparedValue b)
type EdgeFields b = IR.EdgeFields b (IR.RemoteSelect UnpreparedValue) (UnpreparedValue b)
data RemoteRelationshipQueryContext = RemoteRelationshipQueryContext
{ _rrscIntrospectionResultOriginal :: !IntrospectionResult,
_rrscParsedIntrospection :: !ParsedIntrospection,
_rrscRemoteSchemaCustomizer :: !RemoteSchemaCustomizer
}
data QueryContext = QueryContext
{ qcStringifyNum :: !Bool,
-- | should boolean fields be collapsed to True when null is given?
qcDangerousBooleanCollapse :: !Bool,
qcQueryType :: !ET.GraphQLQueryType,
qcRemoteRelationshipContext :: !(HashMap RemoteSchemaName RemoteRelationshipQueryContext),
qcFunctionPermsContext :: !FunctionPermissionsCtx
}
textToName :: MonadError QErr m => Text -> m G.Name
textToName textName =
G.mkName textName
`onNothing` throw400
ValidationFailed
( "cannot include " <> textName <<> " in the GraphQL schema because "
<> " it is not a valid GraphQL identifier"
)
partialSQLExpToUnpreparedValue :: PartialSQLExp b -> P.UnpreparedValue b
partialSQLExpToUnpreparedValue (PSESessVar pftype var) = P.UVSessionVar pftype var
partialSQLExpToUnpreparedValue PSESession = P.UVSession
partialSQLExpToUnpreparedValue (PSESQLExp sqlExp) = P.UVLiteral sqlExp
mapField ::
Functor m =>
P.InputFieldsParser m (Maybe a) ->
(a -> b) ->
P.InputFieldsParser m (Maybe b)
mapField fp f = fmap (fmap f) fp
parsedSelectionsToFields ::
-- | how to handle @__typename@ fields
(Text -> a) ->
OMap.InsOrdHashMap G.Name (P.ParsedSelection a) ->
IR.Fields a
parsedSelectionsToFields mkTypename =
OMap.toList
>>> map (FieldName . G.unName *** P.handleTypename (mkTypename . G.unName))
numericAggOperators :: [G.Name]
numericAggOperators =
[ $$(G.litName "sum"),
$$(G.litName "avg"),
$$(G.litName "stddev"),
$$(G.litName "stddev_samp"),
$$(G.litName "stddev_pop"),
$$(G.litName "variance"),
$$(G.litName "var_samp"),
$$(G.litName "var_pop")
]
comparisonAggOperators :: [G.Name]
comparisonAggOperators = [$$(litName "max"), $$(litName "min")]
data NodeIdVersion
= NIVersion1
deriving (Show, Eq)
nodeIdVersionInt :: NodeIdVersion -> Int
nodeIdVersionInt NIVersion1 = 1
currentNodeIdVersion :: NodeIdVersion
currentNodeIdVersion = NIVersion1
instance J.FromJSON NodeIdVersion where
parseJSON v = do
versionInt :: Int <- J.parseJSON v
case versionInt of
1 -> pure NIVersion1
_ -> fail $ "expecting version 1 for node id, but got " <> show versionInt
mkDescriptionWith :: Maybe PG.PGDescription -> Text -> G.Description
mkDescriptionWith descM defaultTxt = G.Description $ case descM of
Nothing -> defaultTxt
Just (PG.PGDescription descTxt) -> T.unlines [descTxt, "\n", defaultTxt]
-- TODO why do we do these validations at this point? What does it mean to track
-- a function but not add it to the schema...?
-- Auke:
-- I believe the intention is simply to allow the console to do postgres data management
-- Karthikeyan: Yes, this is correct. We allowed this pre PDV but somehow
-- got removed in PDV. OTOH, Im not sure how prevalent this feature
-- actually is
takeValidTables :: forall b. Backend b => TableCache b -> TableCache b
takeValidTables = Map.filterWithKey graphQLTableFilter . Map.filter tableFilter
where
tableFilter = not . isSystemDefined . _tciSystemDefined . _tiCoreInfo
graphQLTableFilter tableName tableInfo =
-- either the table name should be GraphQL compliant
-- or it should have a GraphQL custom name set with it
isRight (tableGraphQLName @b tableName)
|| isJust (_tcCustomName $ _tciCustomConfig $ _tiCoreInfo tableInfo)
-- TODO and what about graphql-compliant function names here too?
takeValidFunctions :: forall b. FunctionCache b -> FunctionCache b
takeValidFunctions = Map.filter functionFilter
where
functionFilter = not . isSystemDefined . _fiSystemDefined
-- root field builder helpers
requiredFieldParser ::
(Functor n, Functor m) =>
(a -> b) ->
m (P.FieldParser n a) ->
m (Maybe (P.FieldParser n b))
requiredFieldParser f = fmap $ Just . fmap f
optionalFieldParser ::
(Functor n, Functor m) =>
(a -> b) ->
m (Maybe (P.FieldParser n a)) ->
m (Maybe (P.FieldParser n b))
optionalFieldParser = fmap . fmap . fmap