2022-03-16 03:39:21 +03:00
|
|
|
{-# LANGUAGE TemplateHaskell #-}
|
|
|
|
|
2022-03-03 06:43:27 +03:00
|
|
|
module Hasura.RQL.IR.Action
|
|
|
|
( ActionFieldG (..),
|
|
|
|
ActionFieldsG,
|
|
|
|
ActionFields,
|
|
|
|
ActionRemoteRelationshipSelect (..),
|
|
|
|
_ACFExpression,
|
|
|
|
_ACFNestedObject,
|
|
|
|
_ACFRemote,
|
|
|
|
_ACFScalar,
|
2022-05-14 14:09:29 +03:00
|
|
|
AnnActionExecution (..),
|
|
|
|
aaeName,
|
|
|
|
aaeOutputType,
|
|
|
|
aaeFields,
|
|
|
|
aaePayload,
|
|
|
|
aaeOutputFields,
|
|
|
|
aaeWebhook,
|
|
|
|
aaeHeaders,
|
|
|
|
aaeForwardClientHeaders,
|
|
|
|
aaeTimeOut,
|
|
|
|
aaeRequestTransform,
|
|
|
|
aaeResponseTransform,
|
|
|
|
AnnActionMutationAsync (..),
|
|
|
|
AsyncActionQueryFieldG (..),
|
|
|
|
_AsyncTypename,
|
|
|
|
_AsyncOutput,
|
|
|
|
_AsyncId,
|
|
|
|
_AsyncCreatedAt,
|
|
|
|
_AsyncErrors,
|
|
|
|
AnnActionAsyncQuery (..),
|
|
|
|
aaaqName,
|
|
|
|
aaaqActionId,
|
|
|
|
aaaqOutputType,
|
|
|
|
aaaqFields,
|
|
|
|
aaaqDefinitionList,
|
|
|
|
aaaqStringifyNum,
|
|
|
|
aaaqForwardClientHeaders,
|
|
|
|
aaaqSource,
|
|
|
|
ActionSourceInfo (..),
|
|
|
|
ActionOutputFields,
|
|
|
|
getActionOutputFields,
|
2022-03-03 06:43:27 +03:00
|
|
|
)
|
|
|
|
where
|
|
|
|
|
2022-05-14 14:09:29 +03:00
|
|
|
import Control.Lens (makeLenses, makePrisms)
|
|
|
|
import Data.Aeson qualified as J
|
|
|
|
import Data.HashMap.Strict qualified as Map
|
2022-03-03 06:43:27 +03:00
|
|
|
import Data.Kind (Type)
|
2022-07-14 20:57:28 +03:00
|
|
|
import Hasura.GraphQL.Schema.Options (StringifyNumbers)
|
2022-03-03 06:43:27 +03:00
|
|
|
import Hasura.Prelude
|
2022-05-14 14:09:29 +03:00
|
|
|
import Hasura.RQL.DDL.Headers
|
|
|
|
import Hasura.RQL.DDL.Webhook.Transform (MetadataResponseTransform, RequestTransform)
|
|
|
|
import Hasura.RQL.Types.Action qualified as RQL
|
|
|
|
import Hasura.RQL.Types.Backend
|
2022-07-14 20:57:28 +03:00
|
|
|
import Hasura.RQL.Types.Common (EnvRecord, FieldName, Fields, ResolvedWebhook, SourceName, Timeout)
|
2022-05-14 14:09:29 +03:00
|
|
|
import Hasura.RQL.Types.CustomTypes
|
|
|
|
( AnnotatedObjectType (..),
|
|
|
|
AnnotatedOutputType (..),
|
Move, document, and prune action types and custom types types.
### Description
This PR is a first step in a series of cleanups of action relationships. This first step does not contain any behavioral change, and it simply reorganizes / prunes / rearranges / documents the code. Mainly:
- it divides some files in RQL.Types between metadata types, schema cache types, execution types;
- it renames some types for consistency;
- it minimizes exports and prunes unnecessary types;
- it moves some types in places where they make more sense;
- it replaces uses of `DMap BackendTag` with `BackendMap`.
Most of the "movement" within files re-organizes declarations in a "top-down" fashion, by moving all TH splices to the end of the file, which avoids order or declarations mattering.
### Optional list types
One main type change this PR makes is a replacement of variant list types in `CustomTypes.hs`; we had `Maybe [a]`, or sometimes `Maybe (NonEmpty a)`. This PR harmonizes all of them to `[a]`, as most of the code would use them as such, by doing `fromMaybe []` or `maybe [] toList`.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4613
GitOrigin-RevId: bc624e10df587eba862ff27a5e8021b32d0d78a2
2022-06-07 18:43:34 +03:00
|
|
|
GraphQLType (..),
|
2022-05-14 14:09:29 +03:00
|
|
|
ObjectFieldDefinition (..),
|
|
|
|
ObjectFieldName (..),
|
|
|
|
)
|
|
|
|
import Hasura.SQL.Backend
|
2022-03-03 06:43:27 +03:00
|
|
|
import Language.GraphQL.Draft.Syntax qualified as G
|
|
|
|
|
2022-03-12 04:37:11 +03:00
|
|
|
-- | Internal representation for a selection of fields on the result of an action.
|
|
|
|
-- Type parameter r will be either
|
|
|
|
-- r ~ (RemoteRelationshipField UnpreparedValue) when the AST is emitted by the parser.
|
|
|
|
-- r ~ Void when an execution tree is constructed so that a backend is
|
|
|
|
-- absolved of dealing with remote relationships.
|
2022-03-03 06:43:27 +03:00
|
|
|
data ActionFieldG (r :: Type)
|
2022-03-12 04:37:11 +03:00
|
|
|
= -- | Scalar value. G.Name is the original field name from the object type.
|
|
|
|
ACFScalar G.Name
|
|
|
|
| -- | Remote relationship
|
|
|
|
ACFRemote (ActionRemoteRelationshipSelect r)
|
|
|
|
| -- | Constant text value (used for __typename fields)
|
|
|
|
ACFExpression Text
|
|
|
|
| -- | Nested object. G.Name is the original field name from the object type.
|
2022-08-01 12:32:04 +03:00
|
|
|
ACFNestedObject G.Name (ActionFieldsG r)
|
2022-03-08 11:22:20 +03:00
|
|
|
deriving (Eq, Show, Functor, Foldable, Traversable)
|
2022-03-03 06:43:27 +03:00
|
|
|
|
|
|
|
type ActionFieldsG r = Fields (ActionFieldG r)
|
|
|
|
|
|
|
|
type ActionFields = ActionFieldsG Void
|
|
|
|
|
|
|
|
data ActionRemoteRelationshipSelect r = ActionRemoteRelationshipSelect
|
|
|
|
{ -- | The fields on the table that are required for the join condition
|
|
|
|
-- of the remote relationship
|
|
|
|
_arrsLHSJoinFields :: HashMap FieldName G.Name,
|
|
|
|
-- | The field that captures the relationship
|
|
|
|
-- r ~ (RemoteRelationshipField UnpreparedValue) when the AST is emitted by the parser.
|
|
|
|
-- r ~ Void when an execution tree is constructed so that a backend is
|
|
|
|
-- absolved of dealing with remote relationships.
|
|
|
|
_arrsRelationship :: r
|
|
|
|
}
|
2022-03-08 11:22:20 +03:00
|
|
|
deriving (Eq, Show, Functor, Foldable, Traversable)
|
2022-03-03 06:43:27 +03:00
|
|
|
|
|
|
|
$(makePrisms ''ActionFieldG)
|
2022-05-14 14:09:29 +03:00
|
|
|
|
|
|
|
data AnnActionExecution (r :: Type) = AnnActionExecution
|
2022-08-01 12:32:04 +03:00
|
|
|
{ _aaeName :: RQL.ActionName,
|
2022-05-14 14:09:29 +03:00
|
|
|
-- | output type
|
2022-08-01 12:32:04 +03:00
|
|
|
_aaeOutputType :: GraphQLType,
|
2022-05-14 14:09:29 +03:00
|
|
|
-- | output selection
|
2022-08-01 12:32:04 +03:00
|
|
|
_aaeFields :: (ActionFieldsG r),
|
2022-05-14 14:09:29 +03:00
|
|
|
-- | jsonified input arguments
|
2022-08-01 12:32:04 +03:00
|
|
|
_aaePayload :: J.Value,
|
2022-05-14 14:09:29 +03:00
|
|
|
-- | to validate the response fields from webhook
|
2022-08-01 12:32:04 +03:00
|
|
|
_aaeOutputFields :: ActionOutputFields,
|
|
|
|
_aaeWebhook :: EnvRecord ResolvedWebhook,
|
|
|
|
_aaeHeaders :: [HeaderConf],
|
|
|
|
_aaeForwardClientHeaders :: Bool,
|
|
|
|
_aaeTimeOut :: Timeout,
|
|
|
|
_aaeRequestTransform :: Maybe RequestTransform,
|
|
|
|
_aaeResponseTransform :: Maybe MetadataResponseTransform
|
2022-05-14 14:09:29 +03:00
|
|
|
}
|
|
|
|
deriving stock (Functor, Foldable, Traversable)
|
|
|
|
|
|
|
|
type ActionOutputFields = Map.HashMap G.Name G.GType
|
|
|
|
|
|
|
|
getActionOutputFields :: AnnotatedOutputType -> ActionOutputFields
|
|
|
|
getActionOutputFields inp = case inp of
|
2022-06-23 13:51:21 +03:00
|
|
|
AOTObject aot -> Map.fromList do
|
|
|
|
ObjectFieldDefinition {..} <- toList $ _aotFields aot
|
|
|
|
pure (unObjectFieldName _ofdName, fst _ofdType)
|
2022-05-14 14:09:29 +03:00
|
|
|
AOTScalar _ -> Map.empty
|
|
|
|
|
|
|
|
data AnnActionMutationAsync = AnnActionMutationAsync
|
2022-08-01 12:32:04 +03:00
|
|
|
{ _aamaName :: RQL.ActionName,
|
|
|
|
_aamaForwardClientHeaders :: Bool,
|
2022-05-14 14:09:29 +03:00
|
|
|
-- | jsonified input arguments
|
2022-08-01 12:32:04 +03:00
|
|
|
_aamaPayload :: J.Value
|
2022-05-14 14:09:29 +03:00
|
|
|
}
|
|
|
|
deriving (Show, Eq)
|
|
|
|
|
|
|
|
data AsyncActionQueryFieldG (r :: Type)
|
2022-08-01 12:32:04 +03:00
|
|
|
= AsyncTypename Text
|
|
|
|
| AsyncOutput (ActionFieldsG r)
|
2022-05-14 14:09:29 +03:00
|
|
|
| AsyncId
|
|
|
|
| AsyncCreatedAt
|
|
|
|
| AsyncErrors
|
|
|
|
deriving stock (Functor, Foldable, Traversable)
|
|
|
|
|
|
|
|
type AsyncActionQueryFieldsG r = Fields (AsyncActionQueryFieldG r)
|
|
|
|
|
|
|
|
data AnnActionAsyncQuery (b :: BackendType) (r :: Type) = AnnActionAsyncQuery
|
2022-08-01 12:32:04 +03:00
|
|
|
{ _aaaqName :: RQL.ActionName,
|
|
|
|
_aaaqActionId :: RQL.ActionId,
|
|
|
|
_aaaqOutputType :: GraphQLType,
|
|
|
|
_aaaqFields :: AsyncActionQueryFieldsG r,
|
|
|
|
_aaaqDefinitionList :: [(Column b, ScalarType b)],
|
|
|
|
_aaaqStringifyNum :: StringifyNumbers,
|
|
|
|
_aaaqForwardClientHeaders :: Bool,
|
|
|
|
_aaaqSource :: ActionSourceInfo b
|
2022-05-14 14:09:29 +03:00
|
|
|
}
|
|
|
|
deriving stock (Functor, Foldable, Traversable)
|
|
|
|
|
|
|
|
data ActionSourceInfo b
|
|
|
|
= -- | No relationships defined on the action output object
|
|
|
|
ASINoSource
|
|
|
|
| -- | All relationships refer to tables in one source
|
2022-06-23 13:51:21 +03:00
|
|
|
ASISource SourceName (SourceConfig b)
|
2022-05-14 14:09:29 +03:00
|
|
|
|
|
|
|
$(makeLenses ''AnnActionAsyncQuery)
|
|
|
|
$(makeLenses ''AnnActionExecution)
|
|
|
|
$(makePrisms ''AsyncActionQueryFieldG)
|