graphql-engine/server/src-lib/Hasura/RQL/IR/Action.hs
jkachmar 647231b685 Yeet some default-extensions
Manually enables:
* EmptyCase
* ExistentialQuantification
* QuantifiedConstraints
* QuasiQuotes
* TemplateHaskell
* TypeFamilyDependencies

...in the following components:
* 'graphql-engine' library
* 'graphql-engine' 'src-test'
* 'graphql-engine' 'tests/integration'
* 'graphql-engine' tests-hspec'

Additionally, performs some light refactoring and documentation.

PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3991
GitOrigin-RevId: 514477d3466b01f60eca8935d0fef60dd0756838
2022-03-16 00:40:17 +00:00

54 lines
1.9 KiB
Haskell

{-# LANGUAGE TemplateHaskell #-}
module Hasura.RQL.IR.Action
( ActionFieldG (..),
ActionFieldsG,
ActionFields,
ActionRemoteRelationshipSelect (..),
_ACFExpression,
_ACFNestedObject,
_ACFRemote,
_ACFScalar,
)
where
import Control.Lens.TH (makePrisms)
import Data.Kind (Type)
import Hasura.Prelude
import Hasura.RQL.Types.Common (FieldName, Fields)
import Language.GraphQL.Draft.Syntax qualified as G
-- | 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.
data ActionFieldG (r :: Type)
= -- | 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.
ACFNestedObject G.Name !(ActionFieldsG r)
deriving (Eq, Show, Functor, Foldable, Traversable)
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
}
deriving (Eq, Show, Functor, Foldable, Traversable)
$(makePrisms ''ActionFieldG)