Parse subscriptions

This commit is contained in:
Eugen Wissner 2020-07-11 06:34:10 +02:00
parent 04a58be3f8
commit 840e129c44
7 changed files with 30 additions and 11 deletions

View File

@ -21,6 +21,7 @@ and this project adheres to
- `Error.Error` is an error representation with a message and source location.
- `Error.Response` represents a result of running a GraphQL query.
- `Type.Schema` exports `Type` which lists all types possible in the schema.
- Parsing subscriptions (the execution always fails yet).
## Changed
- `Trans.ActionT` has become to `Type.Out.ResolverT`. Since `Type.Out.Resolver`

View File

@ -99,9 +99,7 @@ data OperationDefinition
-- * mutation - a write operation followed by a fetch.
-- * subscription - a long-lived request that fetches data in response to
-- source events.
--
-- Currently only queries and mutations are supported.
data OperationType = Query | Mutation deriving (Eq, Show)
data OperationType = Query | Mutation | Subscription deriving (Eq, Show)
-- ** Selection Sets

View File

@ -1,5 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE LambdaCase #-}
-- | This module defines a minifier and a printer for the @GraphQL@ language.
module Language.GraphQL.AST.Encoder
@ -65,12 +66,14 @@ definition formatter x
-- | Converts a 'OperationDefinition into a string.
operationDefinition :: Formatter -> OperationDefinition -> Lazy.Text
operationDefinition formatter (SelectionSet sels)
= selectionSet formatter sels
operationDefinition formatter (OperationDefinition Query name vars dirs sels)
= "query " <> node formatter name vars dirs sels
operationDefinition formatter (OperationDefinition Mutation name vars dirs sels)
= "mutation " <> node formatter name vars dirs sels
operationDefinition formatter = \case
SelectionSet sels -> selectionSet formatter sels
OperationDefinition Query name vars dirs sels ->
"query " <> node formatter name vars dirs sels
OperationDefinition Mutation name vars dirs sels ->
"mutation " <> node formatter name vars dirs sels
OperationDefinition Subscription name vars dirs sels ->
"subscription " <> node formatter name vars dirs sels
-- | Converts a Query or Mutation into a string.
node :: Formatter ->

View File

@ -334,7 +334,8 @@ operationDefinition = SelectionSet <$> selectionSet
operationType :: Parser OperationType
operationType = Query <$ symbol "query"
<|> Mutation <$ symbol "mutation"
-- <?> Keep default error message
<|> Subscription <$ symbol "subscription"
<?> "OperationType"
selectionSet :: Parser SelectionSet
selectionSet = braces (NonEmpty.some selection) <?> "SelectionSet"

View File

@ -1,3 +1,5 @@
{-# LANGUAGE OverloadedStrings #-}
-- | This module provides functions to execute a @GraphQL@ request.
module Language.GraphQL.Execute
( execute
@ -42,6 +44,8 @@ executeRequest (Transform.Document types' rootObjectType operation)
executeOperation types' rootObjectType fields
| (Transform.Mutation _ fields) <- operation =
executeOperation types' rootObjectType fields
| otherwise =
pure $ singleError "This service does not support subscriptions."
-- This is actually executeMutation, but we don't distinguish between queries
-- and mutations yet.

View File

@ -77,6 +77,7 @@ data Selection m
data Operation m
= Query (Maybe Text) (Seq (Selection m))
| Mutation (Maybe Text) (Seq (Selection m))
| Subscription (Maybe Text) (Seq (Selection m))
-- | Single GraphQL field.
data Field m = Field
@ -275,6 +276,8 @@ operation operationDefinition replacement
Query name <$> appendSelection sels
transform (OperationDefinition Full.Mutation name _ _ sels) =
Mutation name <$> appendSelection sels
transform (OperationDefinition Full.Subscription name _ _ sels) =
Subscription name <$> appendSelection sels
-- * Selection

View File

@ -159,3 +159,12 @@ spec = describe "Parser" $ do
queryField: String
}
|]
it "parses subscriptions" $
parse document "" `shouldSucceedOn` [r|
subscription NewMessages {
newMessage(roomId: 123) {
sender
}
}
|]