Compare commits

..

No commits in common. "master" and "master" have entirely different histories.

22 changed files with 251 additions and 343 deletions

View File

@ -1,3 +0,0 @@
END {
system("cabal upload --username belka --password "ENVIRON["HACKAGE_PASSWORD"]" "$0)
}

View File

@ -2,32 +2,67 @@ name: Build
on: on:
push: push:
branches:
- '**'
pull_request: pull_request:
branches: [master] branches: [master]
jobs: jobs:
audit: audit:
runs-on: buildenv runs-on: alpine
steps: steps:
- name: Set up environment
shell: ash {0}
run: |
apk add --no-cache git bash curl build-base readline-dev openssl-dev zlib-dev libpq-dev gmp-dev
- name: Prepare system
run: |
curl --create-dirs --output-dir \
~/.ghcup/bin https://downloads.haskell.org/~ghcup/0.1.19.5/x86_64-linux-ghcup-0.1.19.5 -o ghcup
chmod +x ~/.ghcup/bin/ghcup
~/.ghcup/bin/ghcup install ghc 9.4.8
~/.ghcup/bin/ghcup install cabal 3.6.2.0
- uses: actions/checkout@v4 - uses: actions/checkout@v4
- run: hlint -- src tests - name: Install dependencies
run: |
~/.ghcup/bin/ghcup run --ghc 9.4.8 --cabal 3.6.2.0 -- cabal update
~/.ghcup/bin/ghcup run --ghc 9.4.8 --cabal 3.6.2.0 -- cabal install hlint --constraint="hlint ==3.6.1"
- run: ~/.cabal/bin/hlint -- src tests
test: test:
runs-on: buildenv runs-on: alpine
steps: steps:
- name: Set up environment
shell: ash {0}
run: |
apk add --no-cache git bash curl build-base readline-dev openssl-dev zlib-dev libpq-dev gmp-dev
- name: Prepare system
run: |
curl --create-dirs --output-dir \
~/.ghcup/bin https://downloads.haskell.org/~ghcup/0.1.19.5/x86_64-linux-ghcup-0.1.19.5 -o ghcup
chmod +x ~/.ghcup/bin/ghcup
~/.ghcup/bin/ghcup install ghc 9.4.8
~/.ghcup/bin/ghcup install cabal 3.6.2.0
- uses: actions/checkout@v4 - uses: actions/checkout@v4
- name: Install dependencies - name: Install dependencies
run: cabal update run: |
- name: Prepare system ~/.ghcup/bin/ghcup run --ghc 9.4.8 --cabal 3.6.2.0 -- cabal update
run: cabal build graphql-test ~/.ghcup/bin/ghcup run --ghc 9.4.8 --cabal 3.6.2.0 -- cabal build graphql-test
- run: cabal test --test-show-details=streaming - run: ~/.ghcup/bin/ghcup run --ghc 9.4.8 --cabal 3.6.2.0 -- cabal test --test-show-details=direct
doc: doc:
runs-on: buildenv runs-on: alpine
steps: steps:
- name: Set up environment
shell: ash {0}
run: |
apk add --no-cache git bash curl build-base readline-dev openssl-dev zlib-dev libpq-dev gmp-dev
- name: Prepare system
run: |
curl --create-dirs --output-dir \
~/.ghcup/bin https://downloads.haskell.org/~ghcup/0.1.19.5/x86_64-linux-ghcup-0.1.19.5 -o ghcup
chmod +x ~/.ghcup/bin/ghcup
~/.ghcup/bin/ghcup install ghc 9.4.8
~/.ghcup/bin/ghcup install cabal 3.6.2.0
- uses: actions/checkout@v4 - uses: actions/checkout@v4
- name: Install dependencies - name: Install dependencies
run: cabal update run: ~/.ghcup/bin/ghcup run --ghc 9.4.8 --cabal 3.6.2.0 -- cabal update
- run: cabal haddock --enable-documentation - run: ~/.ghcup/bin/ghcup run --ghc 9.4.8 --cabal 3.6.2.0 -- cabal haddock --enable-documentation

View File

@ -1,17 +0,0 @@
name: Release
on:
push:
tags:
- '**'
jobs:
release:
runs-on: buildenv
steps:
- uses: actions/checkout@v4
- name: Upload a candidate
env:
HACKAGE_PASSWORD: ${{ secrets.HACKAGE_PASSWORD }}
run: |
cabal sdist | awk -f .gitea/deploy.awk

View File

@ -7,31 +7,10 @@ and this project adheres to
[Haskell Package Versioning Policy](https://pvp.haskell.org/). [Haskell Package Versioning Policy](https://pvp.haskell.org/).
## [Unreleased] ## [Unreleased]
### Changed
- `Schema.Directive` is extended to contain a boolean argument, representing
repeatable directives. The parser can parse repeatable directive definitions.
### Fixed
- `gql` quasi quoter recognizeds all GraphQL line endings (CR, LF and CRLF).
### Added
- @specifiedBy directive.
## [1.3.0.0] - 2024-05-01
### Changed
- Remove deprecated `runCollectErrs`, `Resolution`, `CollectErrsT` from the
`Error` module.
## [1.2.0.3] - 2024-01-09
### Fixed
- Fix corrupted source distribution.
## [1.2.0.2] - 2024-01-09
### Fixed ### Fixed
- `gql` removes not only leading `\n` but also `\r`. - `gql` removes not only leading `\n` but also `\r`.
- Fix non nullable type string representation in executor error messages. - Fix non nullable type string representation in executor error messages.
- Fix input objects not being coerced to lists. - Fix input objects not being coerced to lists.
- Fix used variables are not found in the properties of input objects.
## [1.2.0.1] - 2023-04-25 ## [1.2.0.1] - 2023-04-25
### Fixed ### Fixed
@ -535,10 +514,7 @@ and this project adheres to
### Added ### Added
- Data types for the GraphQL language. - Data types for the GraphQL language.
[Unreleased]: https://git.caraus.tech/OSS/graphql/compare/v1.3.0.0...master [Unreleased]: https://git.caraus.tech/OSS/graphql/compare/v1.2.0.1...master
[1.3.0.0]: https://git.caraus.tech/OSS/graphql/compare/v1.2.0.3...v1.3.0.0
[1.2.0.3]: https://git.caraus.tech/OSS/graphql/compare/v1.2.0.2...v1.2.0.3
[1.2.0.2]: https://git.caraus.tech/OSS/graphql/compare/v1.2.0.1...v1.2.0.2
[1.2.0.1]: https://git.caraus.tech/OSS/graphql/compare/v1.2.0.0...v1.2.0.1 [1.2.0.1]: https://git.caraus.tech/OSS/graphql/compare/v1.2.0.0...v1.2.0.1
[1.2.0.0]: https://git.caraus.tech/OSS/graphql/compare/v1.1.0.0...v1.2.0.0 [1.2.0.0]: https://git.caraus.tech/OSS/graphql/compare/v1.1.0.0...v1.2.0.0
[1.1.0.0]: https://git.caraus.tech/OSS/graphql/compare/v1.0.3.0...v1.1.0.0 [1.1.0.0]: https://git.caraus.tech/OSS/graphql/compare/v1.0.3.0...v1.1.0.0

View File

@ -1,7 +1,7 @@
cabal-version: 3.0 cabal-version: 2.4
name: graphql name: graphql
version: 1.3.0.0 version: 1.2.0.1
synopsis: Haskell GraphQL implementation synopsis: Haskell GraphQL implementation
description: Haskell <https://spec.graphql.org/June2018/ GraphQL> implementation. description: Haskell <https://spec.graphql.org/June2018/ GraphQL> implementation.
category: Language category: Language
@ -11,7 +11,7 @@ author: Danny Navarro <j@dannynavarro.net>,
Matthías Páll Gissurarson <mpg@mpg.is>, Matthías Páll Gissurarson <mpg@mpg.is>,
Sólrún Halla Einarsdóttir <she@mpg.is> Sólrún Halla Einarsdóttir <she@mpg.is>
maintainer: belka@caraus.de maintainer: belka@caraus.de
copyright: (c) 2019-2024 Eugen Wissner, copyright: (c) 2019-2023 Eugen Wissner,
(c) 2015-2017 J. Daniel Navarro (c) 2015-2017 J. Daniel Navarro
license: MPL-2.0 AND BSD-3-Clause license: MPL-2.0 AND BSD-3-Clause
license-files: LICENSE, license-files: LICENSE,
@ -21,7 +21,8 @@ extra-source-files:
CHANGELOG.md CHANGELOG.md
README.md README.md
tested-with: tested-with:
GHC == 9.8.2 GHC == 9.4.7,
GHC == 9.6.3
source-repository head source-repository head
type: git type: git
@ -57,9 +58,9 @@ library
ghc-options: -Wall ghc-options: -Wall
build-depends: build-depends:
base >= 4.15 && < 5, base >= 4.7 && < 5,
conduit ^>= 1.3.4, conduit ^>= 1.3.4,
containers >= 0.6 && < 0.8, containers ^>= 0.6.2,
exceptions ^>= 0.10.4, exceptions ^>= 0.10.4,
megaparsec >= 9.0 && < 10, megaparsec >= 9.0 && < 10,
parser-combinators >= 1.3 && < 2, parser-combinators >= 1.3 && < 2,
@ -84,7 +85,6 @@ test-suite graphql-test
Language.GraphQL.Execute.CoerceSpec Language.GraphQL.Execute.CoerceSpec
Language.GraphQL.Execute.OrderedMapSpec Language.GraphQL.Execute.OrderedMapSpec
Language.GraphQL.ExecuteSpec Language.GraphQL.ExecuteSpec
Language.GraphQL.THSpec
Language.GraphQL.Type.OutSpec Language.GraphQL.Type.OutSpec
Language.GraphQL.Validate.RulesSpec Language.GraphQL.Validate.RulesSpec
Schemas.HeroSchema Schemas.HeroSchema
@ -93,7 +93,7 @@ test-suite graphql-test
ghc-options: -threaded -rtsopts -with-rtsopts=-N -Wall ghc-options: -threaded -rtsopts -with-rtsopts=-N -Wall
build-depends: build-depends:
QuickCheck >= 2.14 && < 2.16, QuickCheck ^>= 2.14.1,
base, base,
conduit, conduit,
exceptions, exceptions,

View File

@ -405,7 +405,7 @@ data TypeSystemDefinition
= SchemaDefinition [Directive] (NonEmpty OperationTypeDefinition) = SchemaDefinition [Directive] (NonEmpty OperationTypeDefinition)
| TypeDefinition TypeDefinition | TypeDefinition TypeDefinition
| DirectiveDefinition | DirectiveDefinition
Description Name ArgumentsDefinition Bool (NonEmpty DirectiveLocation) Description Name ArgumentsDefinition (NonEmpty DirectiveLocation)
deriving (Eq, Show) deriving (Eq, Show)
-- ** Type System Extensions -- ** Type System Extensions

View File

@ -159,12 +159,11 @@ typeSystemDefinition formatter = \case
<> optempty (directives formatter) operationDirectives <> optempty (directives formatter) operationDirectives
<> bracesList formatter (operationTypeDefinition formatter) (NonEmpty.toList operationTypeDefinitions') <> bracesList formatter (operationTypeDefinition formatter) (NonEmpty.toList operationTypeDefinitions')
Full.TypeDefinition typeDefinition' -> typeDefinition formatter typeDefinition' Full.TypeDefinition typeDefinition' -> typeDefinition formatter typeDefinition'
Full.DirectiveDefinition description' name' arguments' repeatable locations Full.DirectiveDefinition description' name' arguments' locations
-> description formatter description' -> description formatter description'
<> "@" <> "@"
<> Lazy.Text.fromStrict name' <> Lazy.Text.fromStrict name'
<> argumentsDefinition formatter arguments' <> argumentsDefinition formatter arguments'
<> (if repeatable then " repeatable" else mempty)
<> " on" <> " on"
<> pipeList formatter (directiveLocation <$> locations) <> pipeList formatter (directiveLocation <$> locations)

View File

@ -29,8 +29,7 @@ module Language.GraphQL.AST.Lexer
, unicodeBOM , unicodeBOM
) where ) where
import Control.Applicative (Alternative(..)) import Control.Applicative (Alternative(..), liftA2)
import qualified Control.Applicative.Combinators.NonEmpty as NonEmpty
import Data.Char (chr, digitToInt, isAsciiLower, isAsciiUpper, ord) import Data.Char (chr, digitToInt, isAsciiLower, isAsciiUpper, ord)
import Data.Foldable (foldl') import Data.Foldable (foldl')
import Data.List (dropWhileEnd) import Data.List (dropWhileEnd)
@ -38,22 +37,22 @@ import qualified Data.List.NonEmpty as NonEmpty
import Data.List.NonEmpty (NonEmpty(..)) import Data.List.NonEmpty (NonEmpty(..))
import Data.Proxy (Proxy(..)) import Data.Proxy (Proxy(..))
import Data.Void (Void) import Data.Void (Void)
import Text.Megaparsec import Text.Megaparsec ( Parsec
( Parsec , (<?>)
, (<?>) , between
, between , chunk
, chunk , chunkToTokens
, chunkToTokens , notFollowedBy
, notFollowedBy , oneOf
, oneOf , option
, option , optional
, optional , satisfy
, satisfy , sepBy
, skipSome , skipSome
, takeP , takeP
, takeWhile1P , takeWhile1P
, try , try
) )
import Text.Megaparsec.Char (char, digitChar, space1) import Text.Megaparsec.Char (char, digitChar, space1)
import qualified Text.Megaparsec.Char.Lexer as Lexer import qualified Text.Megaparsec.Char.Lexer as Lexer
import Data.Text (Text) import Data.Text (Text)
@ -143,13 +142,12 @@ blockString :: Parser T.Text
blockString = between "\"\"\"" "\"\"\"" stringValue <* spaceConsumer blockString = between "\"\"\"" "\"\"\"" stringValue <* spaceConsumer
where where
stringValue = do stringValue = do
byLine <- NonEmpty.sepBy1 (many blockStringCharacter) lineTerminator byLine <- sepBy (many blockStringCharacter) lineTerminator
let indentSize = foldr countIndent 0 $ NonEmpty.tail byLine let indentSize = foldr countIndent 0 $ tail byLine
withoutIndent = NonEmpty.head byLine withoutIndent = head byLine : (removeIndent indentSize <$> tail byLine)
: (removeIndent indentSize <$> NonEmpty.tail byLine)
withoutEmptyLines = liftA2 (.) dropWhile dropWhileEnd removeEmptyLine withoutIndent withoutEmptyLines = liftA2 (.) dropWhile dropWhileEnd removeEmptyLine withoutIndent
pure $ T.intercalate "\n" $ T.concat <$> withoutEmptyLines return $ T.intercalate "\n" $ T.concat <$> withoutEmptyLines
removeEmptyLine [] = True removeEmptyLine [] = True
removeEmptyLine [x] = T.null x || isWhiteSpace (T.head x) removeEmptyLine [x] = T.null x || isWhiteSpace (T.head x)
removeEmptyLine _ = False removeEmptyLine _ = False
@ -182,10 +180,10 @@ name :: Parser T.Text
name = do name = do
firstLetter <- nameFirstLetter firstLetter <- nameFirstLetter
rest <- many $ nameFirstLetter <|> digitChar rest <- many $ nameFirstLetter <|> digitChar
void spaceConsumer _ <- spaceConsumer
pure $ TL.toStrict $ TL.cons firstLetter $ TL.pack rest return $ TL.toStrict $ TL.cons firstLetter $ TL.pack rest
where where
nameFirstLetter = satisfy isAsciiUpper <|> satisfy isAsciiLower <|> char '_' nameFirstLetter = satisfy isAsciiUpper <|> satisfy isAsciiLower <|> char '_'
isChunkDelimiter :: Char -> Bool isChunkDelimiter :: Char -> Bool
isChunkDelimiter = flip notElem ['"', '\\', '\n', '\r'] isChunkDelimiter = flip notElem ['"', '\\', '\n', '\r']
@ -199,25 +197,25 @@ lineTerminator = chunk "\r\n" <|> chunk "\n" <|> chunk "\r"
isSourceCharacter :: Char -> Bool isSourceCharacter :: Char -> Bool
isSourceCharacter = isSourceCharacter' . ord isSourceCharacter = isSourceCharacter' . ord
where where
isSourceCharacter' code isSourceCharacter' code = code >= 0x0020
= code >= 0x0020 || code == 0x0009
|| elem code [0x0009, 0x000a, 0x000d] || code == 0x000a
|| code == 0x000d
escapeSequence :: Parser Char escapeSequence :: Parser Char
escapeSequence = do escapeSequence = do
void $ char '\\' _ <- char '\\'
escaped <- oneOf ['"', '\\', '/', 'b', 'f', 'n', 'r', 't', 'u'] escaped <- oneOf ['"', '\\', '/', 'b', 'f', 'n', 'r', 't', 'u']
case escaped of case escaped of
'b' -> pure '\b' 'b' -> return '\b'
'f' -> pure '\f' 'f' -> return '\f'
'n' -> pure '\n' 'n' -> return '\n'
'r' -> pure '\r' 'r' -> return '\r'
't' -> pure '\t' 't' -> return '\t'
'u' -> chr 'u' -> chr . foldl' step 0
. foldl' step 0 . chunkToTokens (Proxy :: Proxy T.Text)
. chunkToTokens (Proxy :: Proxy T.Text) <$> takeP Nothing 4
<$> takeP Nothing 4 _ -> return escaped
_ -> pure escaped
where where
step accumulator = (accumulator * 16 +) . digitToInt step accumulator = (accumulator * 16 +) . digitToInt

View File

@ -8,7 +8,7 @@ module Language.GraphQL.AST.Parser
( document ( document
) where ) where
import Control.Applicative (Alternative(..), optional) import Control.Applicative (Alternative(..), liftA2, optional)
import Control.Applicative.Combinators (sepBy1) import Control.Applicative.Combinators (sepBy1)
import qualified Control.Applicative.Combinators.NonEmpty as NonEmpty import qualified Control.Applicative.Combinators.NonEmpty as NonEmpty
import Data.List.NonEmpty (NonEmpty(..)) import Data.List.NonEmpty (NonEmpty(..))
@ -27,7 +27,6 @@ import Text.Megaparsec
, unPos , unPos
, (<?>) , (<?>)
) )
import Data.Maybe (isJust)
-- | Parser for the GraphQL documents. -- | Parser for the GraphQL documents.
document :: Parser Full.Document document :: Parser Full.Document
@ -83,7 +82,6 @@ directiveDefinition description' = Full.DirectiveDefinition description'
<* at <* at
<*> name <*> name
<*> argumentsDefinition <*> argumentsDefinition
<*> (isJust <$> optional (symbol "repeatable"))
<* symbol "on" <* symbol "on"
<*> directiveLocations <*> directiveLocations
<?> "DirectiveDefinition" <?> "DirectiveDefinition"

View File

@ -8,22 +8,28 @@
-- | Error handling. -- | Error handling.
module Language.GraphQL.Error module Language.GraphQL.Error
( Error(..) ( CollectErrsT
, Error(..)
, Path(..) , Path(..)
, Resolution(..)
, ResolverException(..) , ResolverException(..)
, Response(..) , Response(..)
, ResponseEventStream , ResponseEventStream
, parseError , parseError
, runCollectErrs
) where ) where
import Conduit import Conduit
import Control.Exception (Exception(..)) import Control.Exception (Exception(..))
import Control.Monad.Trans.State (StateT, runStateT)
import Data.HashMap.Strict (HashMap)
import Data.Sequence (Seq(..), (|>)) import Data.Sequence (Seq(..), (|>))
import qualified Data.Sequence as Seq import qualified Data.Sequence as Seq
import Data.Text (Text) import Data.Text (Text)
import qualified Data.Text as Text import qualified Data.Text as Text
import Language.GraphQL.AST (Location(..)) import Language.GraphQL.AST (Location(..), Name)
import Language.GraphQL.Execute.Coerce import Language.GraphQL.Execute.Coerce
import qualified Language.GraphQL.Type.Schema as Schema
import Prelude hiding (null) import Prelude hiding (null)
import Text.Megaparsec import Text.Megaparsec
( ParseErrorBundle(..) ( ParseErrorBundle(..)
@ -91,3 +97,28 @@ instance Show ResolverException where
show (ResolverException e) = show e show (ResolverException e) = show e
instance Exception ResolverException instance Exception ResolverException
-- * Deprecated
{-# DEPRECATED runCollectErrs "runCollectErrs was part of the old executor and isn't used anymore" #-}
-- | Runs the given query computation, but collects the errors into an error
-- list, which is then sent back with the data.
runCollectErrs :: (Monad m, Serialize a)
=> HashMap Name (Schema.Type m)
-> CollectErrsT m a
-> m (Response a)
runCollectErrs types' res = do
(dat, Resolution{..}) <- runStateT res
$ Resolution{ errors = Seq.empty, types = types' }
pure $ Response dat errors
{-# DEPRECATED Resolution "Resolution was part of the old executor and isn't used anymore" #-}
-- | Executor context.
data Resolution m = Resolution
{ errors :: Seq Error
, types :: HashMap Name (Schema.Type m)
}
{-# DEPRECATED CollectErrsT "CollectErrsT was part of the old executor and isn't used anymore" #-}
-- | A wrapper to pass error messages around.
type CollectErrsT m = StateT (Resolution m) m

View File

@ -561,7 +561,7 @@ coerceArgumentValues argumentDefinitions argumentValues =
$ Full.node <$> argumentValues $ Full.node <$> argumentValues
coerceArgumentValue inputType transform = coerceArgumentValue inputType transform =
coerceInputLiteral inputType $ extractArgumentValue transform coerceInputLiteral inputType $ extractArgumentValue transform
extractArgumentValue (Transform.Int integer) = Type.Int integer extractArgumentValue (Transform.Int integer) = Type.Int integer
extractArgumentValue (Transform.Boolean boolean) = Type.Boolean boolean extractArgumentValue (Transform.Boolean boolean) = Type.Boolean boolean
@ -569,7 +569,7 @@ coerceArgumentValues argumentDefinitions argumentValues =
extractArgumentValue (Transform.Float float) = Type.Float float extractArgumentValue (Transform.Float float) = Type.Float float
extractArgumentValue (Transform.Enum enum) = Type.Enum enum extractArgumentValue (Transform.Enum enum) = Type.Enum enum
extractArgumentValue Transform.Null = Type.Null extractArgumentValue Transform.Null = Type.Null
extractArgumentValue (Transform.List list) = extractArgumentValue (Transform.List list) =
Type.List $ extractArgumentValue <$> list Type.List $ extractArgumentValue <$> list
extractArgumentValue (Transform.Object object) = extractArgumentValue (Transform.Object object) =
Type.Object $ extractArgumentValue <$> object Type.Object $ extractArgumentValue <$> object

View File

@ -12,26 +12,17 @@ import Language.Haskell.TH (Exp(..), Lit(..))
stripIndentation :: String -> String stripIndentation :: String -> String
stripIndentation code = reverse stripIndentation code = reverse
$ dropWhile isLineBreak $ dropNewlines
$ reverse $ reverse
$ unlines $ unlines
$ indent spaces <$> lines' withoutLeadingNewlines $ indent spaces <$> lines withoutLeadingNewlines
where where
indent 0 xs = xs indent 0 xs = xs
indent count (' ' : xs) = indent (count - 1) xs indent count (' ' : xs) = indent (count - 1) xs
indent _ xs = xs indent _ xs = xs
withoutLeadingNewlines = dropWhile isLineBreak code withoutLeadingNewlines = dropNewlines code
dropNewlines = dropWhile $ flip any ['\n', '\r'] . (==)
spaces = length $ takeWhile (== ' ') withoutLeadingNewlines spaces = length $ takeWhile (== ' ') withoutLeadingNewlines
lines' "" = []
lines' string =
let (line, rest) = break isLineBreak string
reminder =
case rest of
[] -> []
'\r' : '\n' : strippedString -> lines' strippedString
_ : strippedString -> lines' strippedString
in line : reminder
isLineBreak = flip any ['\n', '\r'] . (==)
-- | Removes leading and trailing newlines. Indentation of the first line is -- | Removes leading and trailing newlines. Indentation of the first line is
-- removed from each line of the string. -- removed from each line of the string.

View File

@ -74,7 +74,6 @@ instance Show Type where
-- | Field argument definition. -- | Field argument definition.
data Argument = Argument (Maybe Text) Type (Maybe Definition.Value) data Argument = Argument (Maybe Text) Type (Maybe Definition.Value)
deriving Eq
-- | Field argument definitions. -- | Field argument definitions.
type Arguments = HashMap Name Argument type Arguments = HashMap Name Argument

View File

@ -48,11 +48,7 @@ data Type m
deriving Eq deriving Eq
-- | Directive definition. -- | Directive definition.
-- data Directive = Directive (Maybe Text) [DirectiveLocation] In.Arguments
-- A definition consists of an optional description, arguments, whether the
-- directive is repeatable, and the allowed directive locations.
data Directive = Directive (Maybe Text) In.Arguments Bool [DirectiveLocation]
deriving Eq
-- | Directive definitions. -- | Directive definitions.
type Directives = HashMap Full.Name Directive type Directives = HashMap Full.Name Directive

View File

@ -85,16 +85,15 @@ schemaWithTypes description' queryRoot mutationRoot subscriptionRoot types' dire
[ ("skip", skipDirective) [ ("skip", skipDirective)
, ("include", includeDirective) , ("include", includeDirective)
, ("deprecated", deprecatedDirective) , ("deprecated", deprecatedDirective)
, ("specifiedBy", specifiedByDirective)
] ]
includeDirective = includeDirective =
Directive includeDescription includeArguments False skipIncludeLocations Directive includeDescription skipIncludeLocations includeArguments
includeArguments = HashMap.singleton "if" includeArguments = HashMap.singleton "if"
$ In.Argument (Just "Included when true.") ifType Nothing $ In.Argument (Just "Included when true.") ifType Nothing
includeDescription = Just includeDescription = Just
"Directs the executor to include this field or fragment only when the \ "Directs the executor to include this field or fragment only when the \
\`if` argument is true." \`if` argument is true."
skipDirective = Directive skipDescription skipArguments False skipIncludeLocations skipDirective = Directive skipDescription skipIncludeLocations skipArguments
skipArguments = HashMap.singleton "if" skipArguments = HashMap.singleton "if"
$ In.Argument (Just "skipped when true.") ifType Nothing $ In.Argument (Just "skipped when true.") ifType Nothing
ifType = In.NonNullScalarType Definition.boolean ifType = In.NonNullScalarType Definition.boolean
@ -107,15 +106,16 @@ schemaWithTypes description' queryRoot mutationRoot subscriptionRoot types' dire
, ExecutableDirectiveLocation DirectiveLocation.InlineFragment , ExecutableDirectiveLocation DirectiveLocation.InlineFragment
] ]
deprecatedDirective = deprecatedDirective =
Directive deprecatedDescription deprecatedArguments False deprecatedLocations Directive deprecatedDescription deprecatedLocations deprecatedArguments
reasonDescription = Just reasonDescription = Just
"Explains why this element was deprecated, usually also including a \ "Explains why this element was deprecated, usually also including a \
\suggestion for how to access supported similar data. Formatted using \ \suggestion for how to access supported similar data. Formatted using \
\the Markdown syntax, as specified by \ \the Markdown syntax, as specified by \
\[CommonMark](https://commonmark.org/).'" \[CommonMark](https://commonmark.org/).'"
deprecatedArguments = HashMap.singleton "reason" deprecatedArguments = HashMap.singleton "reason"
$ In.Argument reasonDescription (In.NamedScalarType Definition.string) $ In.Argument reasonDescription reasonType
$ Just "No longer supported" $ Just "No longer supported"
reasonType = In.NamedScalarType Definition.string
deprecatedDescription = Just deprecatedDescription = Just
"Marks an element of a GraphQL schema as no longer supported." "Marks an element of a GraphQL schema as no longer supported."
deprecatedLocations = deprecatedLocations =
@ -124,16 +124,6 @@ schemaWithTypes description' queryRoot mutationRoot subscriptionRoot types' dire
, TypeSystemDirectiveLocation DirectiveLocation.InputFieldDefinition , TypeSystemDirectiveLocation DirectiveLocation.InputFieldDefinition
, TypeSystemDirectiveLocation DirectiveLocation.EnumValue , TypeSystemDirectiveLocation DirectiveLocation.EnumValue
] ]
specifiedByDirective =
Directive specifiedByDescription specifiedByArguments False specifiedByLocations
urlDescription = Just
"The URL that specifies the behavior of this scalar."
specifiedByArguments = HashMap.singleton "url"
$ In.Argument urlDescription (In.NonNullScalarType Definition.string) Nothing
specifiedByDescription = Just
"Exposes a URL that specifies the behavior of this scalar."
specifiedByLocations =
[TypeSystemDirectiveLocation DirectiveLocation.Scalar]
-- | Traverses the schema and finds all referenced types. -- | Traverses the schema and finds all referenced types.
collectReferencedTypes :: forall m collectReferencedTypes :: forall m

View File

@ -200,7 +200,7 @@ typeSystemDefinition context rule = \case
directives context rule schemaLocation directives' directives context rule schemaLocation directives'
Full.TypeDefinition typeDefinition' -> Full.TypeDefinition typeDefinition' ->
typeDefinition context rule typeDefinition' typeDefinition context rule typeDefinition'
Full.DirectiveDefinition _ _ arguments' _ _ -> Full.DirectiveDefinition _ _ arguments' _ ->
argumentsDefinition context rule arguments' argumentsDefinition context rule arguments'
typeDefinition :: forall m. Validation m -> ApplyRule m Full.TypeDefinition typeDefinition :: forall m. Validation m -> ApplyRule m Full.TypeDefinition
@ -482,4 +482,4 @@ directive context rule (Full.Directive directiveName arguments' _) =
$ Validation.schema context $ Validation.schema context
in arguments rule argumentTypes arguments' in arguments rule argumentTypes arguments'
where where
directiveArguments (Schema.Directive _ argumentTypes _ _) = argumentTypes directiveArguments (Schema.Directive _ _ argumentTypes) = argumentTypes

View File

@ -2,13 +2,11 @@
v. 2.0. If a copy of the MPL was not distributed with this file, You can v. 2.0. If a copy of the MPL was not distributed with this file, You can
obtain one at https://mozilla.org/MPL/2.0/. -} obtain one at https://mozilla.org/MPL/2.0/. -}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE LambdaCase #-} {-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ViewPatterns #-} {-# LANGUAGE ViewPatterns #-}
-- | This module contains default rules defined in the GraphQL specification. -- | This module contains default rules defined in the GraphQL specification.
@ -50,21 +48,19 @@ import Control.Monad.Trans.Class (MonadTrans(..))
import Control.Monad.Trans.Reader (ReaderT(..), ask, asks, mapReaderT) import Control.Monad.Trans.Reader (ReaderT(..), ask, asks, mapReaderT)
import Control.Monad.Trans.State (StateT, evalStateT, gets, modify) import Control.Monad.Trans.State (StateT, evalStateT, gets, modify)
import Data.Bifunctor (first) import Data.Bifunctor (first)
import Data.Foldable (Foldable(..), find) import Data.Foldable (find, fold, foldl', toList)
import qualified Data.HashMap.Strict as HashMap import qualified Data.HashMap.Strict as HashMap
import Data.HashMap.Strict (HashMap) import Data.HashMap.Strict (HashMap)
import Data.HashSet (HashSet) import Data.HashSet (HashSet)
import qualified Data.HashSet as HashSet import qualified Data.HashSet as HashSet
import Data.List (sortBy) import Data.List (groupBy, sortBy, sortOn)
import Data.Maybe (fromMaybe, isJust, isNothing, mapMaybe) import Data.Maybe (fromMaybe, isJust, isNothing, mapMaybe)
import Data.List.NonEmpty (NonEmpty(..)) import Data.List.NonEmpty (NonEmpty(..))
import qualified Data.List.NonEmpty as NonEmpty
import Data.Ord (comparing) import Data.Ord (comparing)
import Data.Sequence (Seq(..), (|>)) import Data.Sequence (Seq(..), (|>))
import qualified Data.Sequence as Seq import qualified Data.Sequence as Seq
import Data.Text (Text) import Data.Text (Text)
import qualified Data.Text as Text import qualified Data.Text as Text
import GHC.Records (HasField(..))
import qualified Language.GraphQL.AST.Document as Full import qualified Language.GraphQL.AST.Document as Full
import qualified Language.GraphQL.Type.Definition as Definition import qualified Language.GraphQL.Type.Definition as Definition
import qualified Language.GraphQL.Type.Internal as Type import qualified Language.GraphQL.Type.Internal as Type
@ -254,16 +250,14 @@ findDuplicates :: (Full.Definition -> [Full.Location] -> [Full.Location])
-> Full.Location -> Full.Location
-> String -> String
-> RuleT m -> RuleT m
findDuplicates filterByName thisLocation errorMessage = findDuplicates filterByName thisLocation errorMessage = do
asks ast >>= go . foldr filterByName [] ast' <- asks ast
let locations' = foldr filterByName [] ast'
if length locations' > 1 && head locations' == thisLocation
then pure $ error' locations'
else lift mempty
where where
go locations' = error' locations' = Error
case locations' of
headLocation : otherLocations -- length locations' > 1
| not $ null otherLocations
, headLocation == thisLocation -> pure $ makeError locations'
_ -> lift mempty
makeError locations' = Error
{ message = errorMessage { message = errorMessage
, locations = locations' , locations = locations'
} }
@ -539,6 +533,11 @@ uniqueDirectiveNamesRule = DirectivesRule
extract (Full.Directive directiveName _ location') = extract (Full.Directive directiveName _ location') =
(directiveName, location') (directiveName, location')
groupSorted :: forall a. (a -> Text) -> [a] -> [[a]]
groupSorted getName = groupBy equalByName . sortOn getName
where
equalByName lhs rhs = getName lhs == getName rhs
filterDuplicates :: forall a filterDuplicates :: forall a
. (a -> (Text, Full.Location)) . (a -> (Text, Full.Location))
-> String -> String
@ -547,12 +546,12 @@ filterDuplicates :: forall a
filterDuplicates extract nodeType = Seq.fromList filterDuplicates extract nodeType = Seq.fromList
. fmap makeError . fmap makeError
. filter ((> 1) . length) . filter ((> 1) . length)
. NonEmpty.groupAllWith getName . groupSorted getName
where where
getName = fst . extract getName = fst . extract
makeError directives' = Error makeError directives' = Error
{ message = makeMessage $ NonEmpty.head directives' { message = makeMessage $ head directives'
, locations = snd . extract <$> toList directives' , locations = snd . extract <$> directives'
} }
makeMessage directive = concat makeMessage directive = concat
[ "There can be only one " [ "There can be only one "
@ -669,16 +668,25 @@ variableUsageDifference difference errorMessage = OperationDefinitionRule $ \cas
= filterSelections' selections = filterSelections' selections
>>= lift . mapReaderT (<> mapDirectives directives') . pure >>= lift . mapReaderT (<> mapDirectives directives') . pure
findDirectiveVariables (Full.Directive _ arguments _) = mapArguments arguments findDirectiveVariables (Full.Directive _ arguments _) = mapArguments arguments
mapArguments = Seq.fromList . (>>= findArgumentVariables) mapArguments = Seq.fromList . (>>= findArgumentVariables)
mapDirectives = foldMap findDirectiveVariables mapDirectives = foldMap findDirectiveVariables
findArgumentVariables (Full.Argument _ value _) = findNodeVariables value findArgumentVariables (Full.Argument _ Full.Node{node = value, ..} _) =
findNodeVariables Full.Node{ node = value, ..} = findValueVariables location value findValueVariables location value
findValueVariables location (Full.Variable value') = [(value', [location])] findValueVariables location (Full.Variable value') = [(value', [location])]
findValueVariables _ (Full.List values) = values >>= findNodeVariables findValueVariables location (Full.List values) =
findValueVariables _ (Full.Object fields) = fields values
>>= findNodeVariables . getField @"value" >>= (\(Full.Node{node = value}) -> findValueVariables location value)
findValueVariables _ (Full.Object fields) =
fields
>>= ( \( Full.ObjectField
{ location = location
, value = Full.Node{node = value}
}
) -> findValueVariables location value
)
findValueVariables _ _ = [] findValueVariables _ _ = []
makeError operationName (variableName, locations') = Error makeError operationName (variableName, locations') = Error
{ message = errorMessage operationName variableName { message = errorMessage operationName variableName
@ -831,7 +839,7 @@ knownArgumentNamesRule = ArgumentsRule fieldRule directiveRule
. Schema.directives . schema . Schema.directives . schema
Full.Argument argumentName _ location' <- lift $ Seq.fromList arguments Full.Argument argumentName _ location' <- lift $ Seq.fromList arguments
case available of case available of
Just (Schema.Directive _ definitions _ _) Just (Schema.Directive _ _ definitions)
| not $ HashMap.member argumentName definitions -> | not $ HashMap.member argumentName definitions ->
pure $ makeError argumentName directiveName location' pure $ makeError argumentName directiveName location'
_ -> lift mempty _ -> lift mempty
@ -911,7 +919,7 @@ directivesInValidLocationsRule = DirectivesRule directivesRule
maybeDefinition <- asks maybeDefinition <- asks
$ HashMap.lookup directiveName . Schema.directives . schema $ HashMap.lookup directiveName . Schema.directives . schema
case maybeDefinition of case maybeDefinition of
Just (Schema.Directive _ _ _ allowedLocations) Just (Schema.Directive _ allowedLocations _)
| directiveLocation `notElem` allowedLocations -> pure $ Error | directiveLocation `notElem` allowedLocations -> pure $ Error
{ message = errorMessage directiveName directiveLocation { message = errorMessage directiveName directiveLocation
, locations = [location] , locations = [location]
@ -941,7 +949,7 @@ providedRequiredArgumentsRule = ArgumentsRule fieldRule directiveRule
available <- asks available <- asks
$ HashMap.lookup directiveName . Schema.directives . schema $ HashMap.lookup directiveName . Schema.directives . schema
case available of case available of
Just (Schema.Directive _ definitions _ _) -> Just (Schema.Directive _ _ definitions) ->
let forEach = go (directiveMessage directiveName) arguments location' let forEach = go (directiveMessage directiveName) arguments location'
in lift $ HashMap.foldrWithKey forEach Seq.empty definitions in lift $ HashMap.foldrWithKey forEach Seq.empty definitions
_ -> lift mempty _ -> lift mempty
@ -1409,7 +1417,7 @@ variablesInAllowedPositionRule = OperationDefinitionRule $ \case
let Full.Directive directiveName arguments _ = directive let Full.Directive directiveName arguments _ = directive
directiveDefinitions <- lift $ asks $ Schema.directives . schema directiveDefinitions <- lift $ asks $ Schema.directives . schema
case HashMap.lookup directiveName directiveDefinitions of case HashMap.lookup directiveName directiveDefinitions of
Just (Schema.Directive _ directiveArguments _ _) -> Just (Schema.Directive _ _ directiveArguments) ->
mapArguments variables directiveArguments arguments mapArguments variables directiveArguments arguments
Nothing -> pure mempty Nothing -> pure mempty
mapArguments variables argumentTypes = fmap fold mapArguments variables argumentTypes = fmap fold

View File

@ -7,7 +7,6 @@ import Test.QuickCheck.Arbitrary (Arbitrary (arbitrary))
import Test.QuickCheck (oneof, elements, listOf, resize, NonEmptyList (..)) import Test.QuickCheck (oneof, elements, listOf, resize, NonEmptyList (..))
import Test.QuickCheck.Gen (Gen (..)) import Test.QuickCheck.Gen (Gen (..))
import Data.Text (Text, pack) import Data.Text (Text, pack)
import Data.Functor ((<&>))
newtype AnyPrintableChar = AnyPrintableChar { getAnyPrintableChar :: Char } deriving (Eq, Show) newtype AnyPrintableChar = AnyPrintableChar { getAnyPrintableChar :: Char } deriving (Eq, Show)
@ -60,36 +59,34 @@ instance Arbitrary a => Arbitrary (AnyObjectField a) where
location' <- getAnyLocation <$> arbitrary location' <- getAnyLocation <$> arbitrary
pure $ AnyObjectField $ Doc.ObjectField name' value' location' pure $ AnyObjectField $ Doc.ObjectField name' value' location'
newtype AnyValue = AnyValue { getAnyValue :: Doc.Value } newtype AnyValue = AnyValue { getAnyValue :: Doc.Value } deriving (Eq, Show)
deriving (Eq, Show)
instance Arbitrary AnyValue instance Arbitrary AnyValue where
where arbitrary = AnyValue <$> oneof
arbitrary = [ variableGen
let variableGen :: Gen Doc.Value , Doc.Int <$> arbitrary
variableGen = Doc.Variable . getAnyName <$> arbitrary , Doc.Float <$> arbitrary
listGen :: Gen [Doc.Node Doc.Value] , Doc.String <$> (getAnyPrintableText <$> arbitrary)
listGen = (resize 5 . listOf) nodeGen , Doc.Boolean <$> arbitrary
nodeGen :: Gen (Doc.Node Doc.Value) , MkGen $ \_ _ -> Doc.Null
nodeGen = fmap getAnyNode arbitrary <&> fmap getAnyValue , Doc.Enum <$> (getAnyName <$> arbitrary)
objectGen :: Gen [Doc.ObjectField Doc.Value] , Doc.List <$> listGen
objectGen = resize 1 , Doc.Object <$> objectGen
$ fmap getNonEmpty arbitrary ]
<&> map (fmap getAnyValue . getAnyObjectField) where
in AnyValue <$> oneof variableGen :: Gen Doc.Value
[ variableGen variableGen = Doc.Variable <$> (getAnyName <$> arbitrary)
, Doc.Int <$> arbitrary listGen :: Gen [Doc.Node Doc.Value]
, Doc.Float <$> arbitrary listGen = (resize 5 . listOf) nodeGen
, Doc.String . getAnyPrintableText <$> arbitrary nodeGen = do
, Doc.Boolean <$> arbitrary node' <- getAnyNode <$> (arbitrary :: Gen (AnyNode AnyValue))
, MkGen $ \_ _ -> Doc.Null pure (getAnyValue <$> node')
, Doc.Enum . getAnyName <$> arbitrary objectGen :: Gen [Doc.ObjectField Doc.Value]
, Doc.List <$> listGen objectGen = resize 1 $ do
, Doc.Object <$> objectGen list <- getNonEmpty <$> (arbitrary :: Gen (NonEmptyList (AnyObjectField AnyValue)))
] pure $ map (fmap getAnyValue . getAnyObjectField) list
newtype AnyArgument a = AnyArgument { getAnyArgument :: Doc.Argument } newtype AnyArgument a = AnyArgument { getAnyArgument :: Doc.Argument } deriving (Eq, Show)
deriving (Eq, Show)
instance Arbitrary a => Arbitrary (AnyArgument a) where instance Arbitrary a => Arbitrary (AnyArgument a) where
arbitrary = do arbitrary = do

View File

@ -11,7 +11,6 @@ import Language.GraphQL.TH
import Test.Hspec (Spec, context, describe, it, shouldBe, shouldStartWith, shouldEndWith, shouldNotContain) import Test.Hspec (Spec, context, describe, it, shouldBe, shouldStartWith, shouldEndWith, shouldNotContain)
import Test.QuickCheck (choose, oneof, forAll) import Test.QuickCheck (choose, oneof, forAll)
import qualified Data.Text.Lazy as Text.Lazy import qualified Data.Text.Lazy as Text.Lazy
import qualified Language.GraphQL.AST.DirectiveLocation as DirectiveLocation
spec :: Spec spec :: Spec
spec = do spec = do
@ -268,26 +267,3 @@ spec = do
|] |]
actual = typeSystemDefinition pretty definition' actual = typeSystemDefinition pretty definition'
in actual `shouldBe` expected in actual `shouldBe` expected
context "directive definition" $ do
it "encodes a directive definition" $ do
let definition' = Full.DirectiveDefinition mempty "example" mempty False
$ pure
$ DirectiveLocation.ExecutableDirectiveLocation DirectiveLocation.Field
expected = [gql|
@example() on
| FIELD
|]
actual = typeSystemDefinition pretty definition'
in actual `shouldBe` expected
it "encodes a repeatable directive definition" $ do
let definition' = Full.DirectiveDefinition mempty "example" mempty True
$ pure
$ DirectiveLocation.ExecutableDirectiveLocation DirectiveLocation.Field
expected = [gql|
@example() repeatable on
| FIELD
|]
actual = typeSystemDefinition pretty definition'
in actual `shouldBe` expected

View File

@ -12,12 +12,7 @@ import qualified Language.GraphQL.AST.DirectiveLocation as DirLoc
import Language.GraphQL.AST.Parser import Language.GraphQL.AST.Parser
import Language.GraphQL.TH import Language.GraphQL.TH
import Test.Hspec (Spec, describe, it, context) import Test.Hspec (Spec, describe, it, context)
import Test.Hspec.Megaparsec import Test.Hspec.Megaparsec (shouldParse, shouldFailOn, shouldSucceedOn)
( shouldParse
, shouldFailOn
, parseSatisfies
, shouldSucceedOn
)
import Text.Megaparsec (parse) import Text.Megaparsec (parse)
import Test.QuickCheck (property, NonEmptyList (..), mapSize) import Test.QuickCheck (property, NonEmptyList (..), mapSize)
import Language.GraphQL.AST.Arbitrary import Language.GraphQL.AST.Arbitrary
@ -75,10 +70,7 @@ spec = describe "Parser" $ do
mutation auth{ mutation auth{
test(username: """username""", password: """password""") test(username: """username""", password: """password""")
}|] }|]
it "fails to parse an empty argument list in parens" $
parse document "" `shouldFailOn` "{ test() }"
it "accepts any arguments" $ mapSize (const 10) $ property $ \xs -> it "accepts any arguments" $ mapSize (const 10) $ property $ \xs ->
let let
query' :: Text query' :: Text
@ -151,20 +143,22 @@ spec = describe "Parser" $ do
|] |]
it "parses two minimal directive definitions" $ it "parses two minimal directive definitions" $
let directive name' loc = TypeSystemDefinition let directive nm loc =
$ DirectiveDefinition TypeSystemDefinition
(Description Nothing) (DirectiveDefinition
name' (Description Nothing)
(ArgumentsDefinition []) nm
False (ArgumentsDefinition [])
(loc :| []) (loc :| []))
example1 = directive "example1" example1 =
(DirLoc.TypeSystemDirectiveLocation DirLoc.FieldDefinition) directive "example1"
(Location {line = 1, column = 1}) (DirLoc.TypeSystemDirectiveLocation DirLoc.FieldDefinition)
example2 = directive "example2" (Location {line = 1, column = 1})
(DirLoc.ExecutableDirectiveLocation DirLoc.Field) example2 =
(Location {line = 2, column = 1}) directive "example2"
testSchemaExtension = example1 :| [example2] (DirLoc.ExecutableDirectiveLocation DirLoc.Field)
(Location {line = 2, column = 1})
testSchemaExtension = example1 :| [ example2 ]
query = [gql| query = [gql|
directive @example1 on FIELD_DEFINITION directive @example1 on FIELD_DEFINITION
directive @example2 on FIELD directive @example2 on FIELD
@ -172,26 +166,31 @@ spec = describe "Parser" $ do
in parse document "" query `shouldParse` testSchemaExtension in parse document "" query `shouldParse` testSchemaExtension
it "parses a directive definition with a default empty list argument" $ it "parses a directive definition with a default empty list argument" $
let argumentValue = Just let directive nm loc args =
$ Node (ConstList []) TypeSystemDefinition
$ Location{ line = 1, column = 33 } (DirectiveDefinition
loc = DirLoc.TypeSystemDirectiveLocation DirLoc.FieldDefinition (Description Nothing)
argumentValueDefinition = InputValueDefinition nm
(Description Nothing) (ArgumentsDefinition
"foo" [ InputValueDefinition
(TypeList (TypeNamed "String")) (Description Nothing)
argumentValue argName
[] argType
definition = DirectiveDefinition argValue
(Description Nothing) []
"test" | (argName, argType, argValue) <- args])
(ArgumentsDefinition [argumentValueDefinition] ) (loc :| []))
False defn =
(loc :| []) directive "test"
directive = TypeSystemDefinition definition (DirLoc.TypeSystemDirectiveLocation DirLoc.FieldDefinition)
$ Location{ line = 1, column = 1 } [("foo",
TypeList (TypeNamed "String"),
Just
$ Node (ConstList [])
$ Location {line = 1, column = 33})]
(Location {line = 1, column = 1})
query = [gql|directive @test(foo: [String] = []) on FIELD_DEFINITION|] query = [gql|directive @test(foo: [String] = []) on FIELD_DEFINITION|]
in parse document "" query `shouldParse` (directive :| []) in parse document "" query `shouldParse` (defn :| [ ])
it "parses schema extension with a new directive" $ it "parses schema extension with a new directive" $
parse document "" `shouldSucceedOn`[gql| parse document "" `shouldSucceedOn`[gql|
@ -211,13 +210,6 @@ spec = describe "Parser" $ do
query = [gql|extend schema @newDirective { query: Query }|] query = [gql|extend schema @newDirective { query: Query }|]
in parse document "" query `shouldParse` (testSchemaExtension :| []) in parse document "" query `shouldParse` (testSchemaExtension :| [])
it "parses a repeatable directive definition" $
let given = [gql|directive @test repeatable on FIELD_DEFINITION|]
isRepeatable (TypeSystemDefinition definition' _ :| [])
| DirectiveDefinition _ _ _ repeatable _ <- definition' = repeatable
isRepeatable _ = False
in parse document "" given `parseSatisfies` isRepeatable
it "parses an object extension" $ it "parses an object extension" $
parse document "" `shouldSucceedOn` [gql| parse document "" `shouldSucceedOn` [gql|
extend type Story { extend type Story {

View File

@ -1,24 +0,0 @@
{- This Source Code Form is subject to the terms of the Mozilla Public License,
v. 2.0. If a copy of the MPL was not distributed with this file, You can
obtain one at https://mozilla.org/MPL/2.0/. -}
{-# LANGUAGE QuasiQuotes #-}
module Language.GraphQL.THSpec
( spec
) where
import Language.GraphQL.TH (gql)
import Test.Hspec (Spec, describe, it, shouldBe)
spec :: Spec
spec =
describe "gql" $
it "replaces CRNL with NL" $
let expected = "line1\nline2\nline3"
actual = [gql|
line1
line2
line3
|]
in actual `shouldBe` expected

View File

@ -18,7 +18,7 @@ import Language.GraphQL.Type
import qualified Language.GraphQL.Type.In as In import qualified Language.GraphQL.Type.In as In
import qualified Language.GraphQL.Type.Out as Out import qualified Language.GraphQL.Type.Out as Out
import Language.GraphQL.Validate import Language.GraphQL.Validate
import Test.Hspec (Spec, context, describe, it, shouldBe, shouldContain) import Test.Hspec (Spec, context, describe, it, shouldBe, shouldContain, xit)
import Text.Megaparsec (parse, errorBundlePretty) import Text.Megaparsec (parse, errorBundlePretty)
petSchema :: Schema IO petSchema :: Schema IO
@ -29,7 +29,6 @@ queryType = ObjectType "Query" Nothing [] $ HashMap.fromList
[ ("dog", dogResolver) [ ("dog", dogResolver)
, ("cat", catResolver) , ("cat", catResolver)
, ("findDog", findDogResolver) , ("findDog", findDogResolver)
, ("findCats", findCatsResolver)
] ]
where where
dogField = Field Nothing (Out.NamedObjectType dogType) mempty dogField = Field Nothing (Out.NamedObjectType dogType) mempty
@ -40,11 +39,6 @@ queryType = ObjectType "Query" Nothing [] $ HashMap.fromList
findDogResolver = ValueResolver findDogField $ pure Null findDogResolver = ValueResolver findDogField $ pure Null
catField = Field Nothing (Out.NamedObjectType catType) mempty catField = Field Nothing (Out.NamedObjectType catType) mempty
catResolver = ValueResolver catField $ pure Null catResolver = ValueResolver catField $ pure Null
findCatsArguments = HashMap.singleton "commands"
$ In.Argument Nothing (In.NonNullListType $ In.NonNullEnumType catCommandType)
$ Just $ List []
findCatsField = Field Nothing (Out.NonNullListType $ Out.NonNullObjectType catType) findCatsArguments
findCatsResolver = ValueResolver findCatsField $ pure $ List []
catCommandType :: EnumType catCommandType :: EnumType
catCommandType = EnumType "CatCommand" Nothing $ HashMap.fromList catCommandType = EnumType "CatCommand" Nothing $ HashMap.fromList
@ -544,7 +538,7 @@ spec =
} }
in validate queryString `shouldContain` [expected] in validate queryString `shouldContain` [expected]
context "noUndefinedVariablesRule" $ do context "noUndefinedVariablesRule" $
it "rejects undefined variables" $ it "rejects undefined variables" $
let queryString = [gql| let queryString = [gql|
query variableIsNotDefinedUsedInSingleFragment { query variableIsNotDefinedUsedInSingleFragment {
@ -566,34 +560,6 @@ spec =
} }
in validate queryString `shouldBe` [expected] in validate queryString `shouldBe` [expected]
it "gets variable location inside an input object" $
let queryString = [gql|
query {
findDog (complex: { name: $name }) {
name
}
}
|]
expected = Error
{ message = "Variable \"$name\" is not defined."
, locations = [AST.Location 2 29]
}
in validate queryString `shouldBe` [expected]
it "gets variable location inside an array" $
let queryString = [gql|
query {
findCats (commands: [JUMP, $command]) {
name
}
}
|]
expected = Error
{ message = "Variable \"$command\" is not defined."
, locations = [AST.Location 2 30]
}
in validate queryString `shouldBe` [expected]
context "noUnusedVariablesRule" $ do context "noUnusedVariablesRule" $ do
it "rejects unused variables" $ it "rejects unused variables" $
let queryString = [gql| let queryString = [gql|
@ -611,7 +577,7 @@ spec =
} }
in validate queryString `shouldBe` [expected] in validate queryString `shouldBe` [expected]
it "detects variables in properties of input objects" $ xit "detects variables in properties of input objects" $
let queryString = [gql| let queryString = [gql|
query withVar ($name: String!) { query withVar ($name: String!) {
findDog (complex: { name: $name }) { findDog (complex: { name: $name }) {