Compare commits

...

16 Commits

Author SHA1 Message Date
fda4b4fce4
Release 1.4.0.0
All checks were successful
Build / audit (push) Successful in 18s
Build / test (push) Successful in 6m9s
Build / doc (push) Successful in 5m6s
Release / release (push) Successful in 5s
2024-10-26 20:03:32 +02:00
5abc377e9d
Deprecate gql
All checks were successful
Build / audit (push) Successful in 17s
Build / test (push) Successful in 6m3s
Build / doc (push) Successful in 5m5s
2024-10-24 16:56:31 +02:00
67720f9ebe
Replace gql with literals in the validation tests
All checks were successful
Build / audit (push) Successful in 19s
Build / test (push) Successful in 6m2s
Build / doc (push) Successful in 5m4s
2024-10-18 21:00:48 +02:00
cdb2aa76b6
Fix block alignment in some parser tests
All checks were successful
Build / audit (push) Successful in 18s
Build / test (push) Successful in 6m4s
Build / doc (push) Successful in 5m5s
2024-10-17 18:08:30 +02:00
b056b4256f
Replace gql in Encoder tests with multiline string
All checks were successful
Build / audit (push) Successful in 17s
Build / test (push) Successful in 6m16s
Build / doc (push) Successful in 5m16s
2024-10-14 20:50:34 +02:00
ba07f8298b
Validate repeatable directives
All checks were successful
Build / audit (push) Successful in 20s
Build / test (push) Successful in 6m7s
Build / doc (push) Successful in 5m5s
2024-10-13 19:40:12 +02:00
1834e5c41e Add a test for empty field argument list
All checks were successful
Build / audit (push) Successful in 17s
Build / test (push) Successful in 6m5s
Build / doc (push) Successful in 5m10s
... within parens.
2024-09-17 18:32:45 +02:00
01b30a71da
Test directive definition decoder
All checks were successful
Build / test (push) Successful in 6m3s
Build / doc (push) Successful in 4m59s
Build / audit (push) Successful in 17s
2024-08-28 20:00:44 +02:00
b40d8a7e1e
Parse repeatable directive definitions
All checks were successful
Build / audit (push) Successful in 18s
Build / test (push) Successful in 6m3s
Build / doc (push) Successful in 4m58s
2024-08-27 10:51:01 +02:00
4b5e25a4d8
Add repeatable argument to the directive
All checks were successful
Build / audit (push) Successful in 17s
Build / test (push) Successful in 5m50s
Build / doc (push) Successful in 5m5s
…  schema representation.
2024-08-25 12:01:48 +02:00
a4e648d5aa
Add specifiedBy directive
All checks were successful
Build / audit (push) Successful in 18s
Build / test (push) Successful in 6m38s
Build / doc (push) Successful in 5m23s
2024-08-23 11:25:54 +02:00
6e32112be4
Require base >=4.15 (GHC 9)
All checks were successful
Build / audit (push) Successful in 19s
Build / test (push) Successful in 8m51s
Build / doc (push) Successful in 7m43s
It's already required by some of the dependencies, so it shouldn't be a
problem. Anyway NonEmpty usage is requiring base >=4.9 at least.
2024-08-07 19:25:42 +02:00
388af30b51
Fix GHC 9.8 warnings
All checks were successful
Build / audit (push) Successful in 16s
Build / test (push) Successful in 6m4s
Build / doc (push) Successful in 4m59s
2024-08-06 18:19:07 +02:00
e02463f452
Remove unused liftA2 import
All checks were successful
Build / audit (push) Successful in 16s
Build / test (push) Successful in 6m12s
Build / doc (push) Successful in 5m15s
2024-08-04 09:06:03 +02:00
9d85379826
Remove cariage return from the qq string
All checks were successful
Build / audit (push) Successful in 16s
Build / test (push) Successful in 6m8s
Build / doc (push) Successful in 5m8s
2024-08-04 08:30:00 +02:00
9b11300d23
Pass sdist output to the upload command
All checks were successful
Build / audit (push) Successful in 16s
Build / test (push) Successful in 6m26s
Build / doc (push) Successful in 5m28s
2024-07-25 12:35:28 +02:00
24 changed files with 842 additions and 884 deletions

3
.gitea/deploy.awk Normal file
View File

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

View File

@ -9,28 +9,14 @@ on:
jobs: jobs:
audit: audit:
runs-on: haskell runs-on: buildenv
steps: steps:
- name: Set up environment
run: |
apt-get update -y
apt-get upgrade -y
apt-get install -y nodejs pkg-config
- uses: actions/checkout@v4 - uses: actions/checkout@v4
- name: Install dependencies - run: hlint -- src tests
run: |
cabal update
cabal install hlint "--constraint=hlint ==3.8"
- run: cabal exec hlint -- src tests
test: test:
runs-on: haskell runs-on: buildenv
steps: steps:
- name: Set up environment
run: |
apt-get update -y
apt-get upgrade -y
apt-get install -y nodejs pkg-config
- uses: actions/checkout@v4 - uses: actions/checkout@v4
- name: Install dependencies - name: Install dependencies
run: cabal update run: cabal update
@ -39,13 +25,8 @@ jobs:
- run: cabal test --test-show-details=streaming - run: cabal test --test-show-details=streaming
doc: doc:
runs-on: haskell runs-on: buildenv
steps: steps:
- name: Set up environment
run: |
apt-get update -y
apt-get upgrade -y
apt-get install -y nodejs pkg-config
- uses: actions/checkout@v4 - uses: actions/checkout@v4
- name: Install dependencies - name: Install dependencies
run: cabal update run: cabal update

View File

@ -7,17 +7,11 @@ on:
jobs: jobs:
release: release:
runs-on: haskell runs-on: buildenv
steps: steps:
- name: Set up environment
run: |
apt-get update -y
apt-get upgrade -y
apt-get install -y nodejs pkg-config
- uses: actions/checkout@v4 - uses: actions/checkout@v4
- name: Upload a candidate - name: Upload a candidate
env: env:
HACKAGE_PASSWORD: ${{ secrets.HACKAGE_PASSWORD }} HACKAGE_PASSWORD: ${{ secrets.HACKAGE_PASSWORD }}
run: | run: |
cabal sdist cabal sdist | awk -f .gitea/deploy.awk
cabal upload --username belka --password ${HACKAGE_PASSWORD}

View File

@ -6,6 +6,20 @@ The format is based on
and this project adheres to and this project adheres to
[Haskell Package Versioning Policy](https://pvp.haskell.org/). [Haskell Package Versioning Policy](https://pvp.haskell.org/).
## [1.4.0.0] - 2024-10-26
### Changed
- `Schema.Directive` is extended to contain a boolean argument, representing
repeatable directives. The parser can parse repeatable directive definitions.
Validation allows repeatable directives.
- `AST.Document.Directive` is a record.
- `gql` quasi quoter is deprecated (moved to graphql-spice package).
### Fixed
- `gql` quasi quoter recognizeds all GraphQL line endings (CR, LF and CRLF).
### Added
- @specifiedBy directive.
## [1.3.0.0] - 2024-05-01 ## [1.3.0.0] - 2024-05-01
### Changed ### Changed
- Remove deprecated `runCollectErrs`, `Resolution`, `CollectErrsT` from the - Remove deprecated `runCollectErrs`, `Resolution`, `CollectErrsT` from the
@ -524,6 +538,7 @@ and this project adheres to
### Added ### Added
- Data types for the GraphQL language. - Data types for the GraphQL language.
[1.4.0.0]: https://git.caraus.tech/OSS/graphql/compare/v1.3.0.0...v1.4.0.0
[1.3.0.0]: https://git.caraus.tech/OSS/graphql/compare/v1.2.0.3...v1.3.0.0 [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.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.2]: https://git.caraus.tech/OSS/graphql/compare/v1.2.0.1...v1.2.0.2

View File

@ -1,7 +1,7 @@
cabal-version: 2.4 cabal-version: 3.0
name: graphql name: graphql
version: 1.3.0.0 version: 1.4.0.0
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
@ -21,8 +21,7 @@ extra-source-files:
CHANGELOG.md CHANGELOG.md
README.md README.md
tested-with: tested-with:
GHC == 9.4.7, GHC == 9.8.2
GHC == 9.6.3
source-repository head source-repository head
type: git type: git
@ -58,7 +57,7 @@ library
ghc-options: -Wall ghc-options: -Wall
build-depends: build-depends:
base >= 4.7 && < 5, base >= 4.15 && < 5,
conduit ^>= 1.3.4, conduit ^>= 1.3.4,
containers >= 0.6 && < 0.8, containers >= 0.6 && < 0.8,
exceptions ^>= 0.10.4, exceptions ^>= 0.10.4,
@ -85,6 +84,7 @@ 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

View File

@ -1,6 +1,6 @@
{-# LANGUAGE Safe #-} {-# LANGUAGE Safe #-}
-- | Various parts of a GraphQL document can be annotated with directives. -- | Various parts of a GraphQL document can be annotated with directives.
-- This module describes locations in a document where directives can appear. -- This module describes locations in a document where directives can appear.
module Language.GraphQL.AST.DirectiveLocation module Language.GraphQL.AST.DirectiveLocation
( DirectiveLocation(..) ( DirectiveLocation(..)

View File

@ -380,7 +380,11 @@ instance Show NonNullType where
-- --
-- Directives begin with "@", can accept arguments, and can be applied to the -- Directives begin with "@", can accept arguments, and can be applied to the
-- most GraphQL elements, providing additional information. -- most GraphQL elements, providing additional information.
data Directive = Directive Name [Argument] Location deriving (Eq, Show) data Directive = Directive
{ name :: Name
, arguments :: [Argument]
, location :: Location
} deriving (Eq, Show)
-- * Type System -- * Type System
@ -405,7 +409,7 @@ data TypeSystemDefinition
= SchemaDefinition [Directive] (NonEmpty OperationTypeDefinition) = SchemaDefinition [Directive] (NonEmpty OperationTypeDefinition)
| TypeDefinition TypeDefinition | TypeDefinition TypeDefinition
| DirectiveDefinition | DirectiveDefinition
Description Name ArgumentsDefinition (NonEmpty DirectiveLocation) Description Name ArgumentsDefinition Bool (NonEmpty DirectiveLocation)
deriving (Eq, Show) deriving (Eq, Show)
-- ** Type System Extensions -- ** Type System Extensions

View File

@ -159,11 +159,12 @@ 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' locations Full.DirectiveDefinition description' name' arguments' repeatable 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)
@ -276,7 +277,7 @@ pipeList :: Foldable t => Formatter -> t Lazy.Text -> Lazy.Text
pipeList Minified = (" " <>) . Lazy.Text.intercalate " | " . toList pipeList Minified = (" " <>) . Lazy.Text.intercalate " | " . toList
pipeList (Pretty _) = Lazy.Text.concat pipeList (Pretty _) = Lazy.Text.concat
. fmap (("\n" <> indentSymbol <> "| ") <>) . fmap (("\n" <> indentSymbol <> "| ") <>)
. toList . toList
enumValueDefinition :: Formatter -> Full.EnumValueDefinition -> Lazy.Text enumValueDefinition :: Formatter -> Full.EnumValueDefinition -> Lazy.Text
enumValueDefinition (Pretty _) enumValue = enumValueDefinition (Pretty _) enumValue =

View File

@ -29,7 +29,8 @@ module Language.GraphQL.AST.Lexer
, unicodeBOM , unicodeBOM
) where ) where
import Control.Applicative (Alternative(..), liftA2) import Control.Applicative (Alternative(..))
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)
@ -37,22 +38,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 ( Parsec import Text.Megaparsec
, (<?>) ( Parsec
, between , (<?>)
, chunk , between
, chunkToTokens , chunk
, notFollowedBy , chunkToTokens
, oneOf , notFollowedBy
, option , oneOf
, optional , option
, satisfy , optional
, sepBy , satisfy
, 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)
@ -142,12 +143,13 @@ blockString :: Parser T.Text
blockString = between "\"\"\"" "\"\"\"" stringValue <* spaceConsumer blockString = between "\"\"\"" "\"\"\"" stringValue <* spaceConsumer
where where
stringValue = do stringValue = do
byLine <- sepBy (many blockStringCharacter) lineTerminator byLine <- NonEmpty.sepBy1 (many blockStringCharacter) lineTerminator
let indentSize = foldr countIndent 0 $ tail byLine let indentSize = foldr countIndent 0 $ NonEmpty.tail byLine
withoutIndent = head byLine : (removeIndent indentSize <$> tail byLine) withoutIndent = NonEmpty.head byLine
: (removeIndent indentSize <$> NonEmpty.tail byLine)
withoutEmptyLines = liftA2 (.) dropWhile dropWhileEnd removeEmptyLine withoutIndent withoutEmptyLines = liftA2 (.) dropWhile dropWhileEnd removeEmptyLine withoutIndent
return $ T.intercalate "\n" $ T.concat <$> withoutEmptyLines pure $ 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
@ -180,10 +182,10 @@ name :: Parser T.Text
name = do name = do
firstLetter <- nameFirstLetter firstLetter <- nameFirstLetter
rest <- many $ nameFirstLetter <|> digitChar rest <- many $ nameFirstLetter <|> digitChar
_ <- spaceConsumer void spaceConsumer
return $ TL.toStrict $ TL.cons firstLetter $ TL.pack rest pure $ 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']
@ -197,25 +199,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 = code >= 0x0020 isSourceCharacter' code
|| code == 0x0009 = code >= 0x0020
|| code == 0x000a || elem code [0x0009, 0x000a, 0x000d]
|| code == 0x000d
escapeSequence :: Parser Char escapeSequence :: Parser Char
escapeSequence = do escapeSequence = do
_ <- char '\\' void $ char '\\'
escaped <- oneOf ['"', '\\', '/', 'b', 'f', 'n', 'r', 't', 'u'] escaped <- oneOf ['"', '\\', '/', 'b', 'f', 'n', 'r', 't', 'u']
case escaped of case escaped of
'b' -> return '\b' 'b' -> pure '\b'
'f' -> return '\f' 'f' -> pure '\f'
'n' -> return '\n' 'n' -> pure '\n'
'r' -> return '\r' 'r' -> pure '\r'
't' -> return '\t' 't' -> pure '\t'
'u' -> chr . foldl' step 0 'u' -> chr
. chunkToTokens (Proxy :: Proxy T.Text) . foldl' step 0
<$> takeP Nothing 4 . chunkToTokens (Proxy :: Proxy T.Text)
_ -> return escaped <$> takeP Nothing 4
_ -> 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(..), liftA2, optional) import Control.Applicative (Alternative(..), 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,6 +27,7 @@ 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
@ -82,6 +83,7 @@ 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

@ -147,7 +147,7 @@ coerceInputLiteral (In.EnumBaseType type') (Type.Enum enumValue)
| member enumValue type' = Just $ Type.Enum enumValue | member enumValue type' = Just $ Type.Enum enumValue
where where
member value (Type.EnumType _ _ members) = HashMap.member value members member value (Type.EnumType _ _ members) = HashMap.member value members
coerceInputLiteral (In.InputObjectBaseType type') (Type.Object values) = coerceInputLiteral (In.InputObjectBaseType type') (Type.Object values) =
let (In.InputObjectType _ _ inputFields) = type' let (In.InputObjectType _ _ inputFields) = type'
in Type.Object in Type.Object
<$> HashMap.foldrWithKey (matchFieldValues' values) (Just HashMap.empty) inputFields <$> HashMap.foldrWithKey (matchFieldValues' values) (Just HashMap.empty) inputFields

View File

@ -12,20 +12,30 @@ import Language.Haskell.TH (Exp(..), Lit(..))
stripIndentation :: String -> String stripIndentation :: String -> String
stripIndentation code = reverse stripIndentation code = reverse
$ dropNewlines $ dropWhile isLineBreak
$ 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 = dropNewlines code withoutLeadingNewlines = dropWhile isLineBreak 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.
{-# DEPRECATED gql "Use Language.GraphQL.Class.gql from graphql-spice instead" #-}
gql :: QuasiQuoter gql :: QuasiQuoter
gql = QuasiQuoter gql = QuasiQuoter
{ quoteExp = pure . LitE . StringL . stripIndentation { quoteExp = pure . LitE . StringL . stripIndentation

View File

@ -74,6 +74,7 @@ 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,7 +48,11 @@ 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,15 +85,16 @@ 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 skipIncludeLocations includeArguments Directive includeDescription includeArguments False skipIncludeLocations
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 skipIncludeLocations skipArguments skipDirective = Directive skipDescription skipArguments False skipIncludeLocations
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
@ -106,16 +107,15 @@ schemaWithTypes description' queryRoot mutationRoot subscriptionRoot types' dire
, ExecutableDirectiveLocation DirectiveLocation.InlineFragment , ExecutableDirectiveLocation DirectiveLocation.InlineFragment
] ]
deprecatedDirective = deprecatedDirective =
Directive deprecatedDescription deprecatedLocations deprecatedArguments Directive deprecatedDescription deprecatedArguments False deprecatedLocations
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 reasonType $ In.Argument reasonDescription (In.NamedScalarType Definition.string)
$ 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,6 +124,16 @@ 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
@ -283,7 +283,7 @@ operationDefinition rule context operation
schema' = Validation.schema context schema' = Validation.schema context
queryRoot = Just $ Out.NamedObjectType $ Schema.query schema' queryRoot = Just $ Out.NamedObjectType $ Schema.query schema'
types' = Schema.types schema' types' = Schema.types schema'
typeToOut :: forall m. Schema.Type m -> Maybe (Out.Type m) typeToOut :: forall m. Schema.Type m -> Maybe (Out.Type m)
typeToOut (Schema.ObjectType objectType) = typeToOut (Schema.ObjectType objectType) =
Just $ Out.NamedObjectType objectType Just $ Out.NamedObjectType objectType
@ -403,7 +403,7 @@ arguments :: forall m
-> Seq (Validation.RuleT m) -> Seq (Validation.RuleT m)
arguments rule argumentTypes = foldMap forEach . Seq.fromList arguments rule argumentTypes = foldMap forEach . Seq.fromList
where where
forEach argument'@(Full.Argument argumentName _ _) = forEach argument'@(Full.Argument argumentName _ _) =
let argumentType = HashMap.lookup argumentName argumentTypes let argumentType = HashMap.lookup argumentName argumentTypes
in argument rule argumentType argument' in argument rule argumentType argument'
@ -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

@ -50,14 +50,15 @@ 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 (find, fold, foldl', toList) import Data.Foldable (Foldable(..), find)
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 (groupBy, sortBy, sortOn) import Data.List (sortBy)
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
@ -253,14 +254,16 @@ findDuplicates :: (Full.Definition -> [Full.Location] -> [Full.Location])
-> Full.Location -> Full.Location
-> String -> String
-> RuleT m -> RuleT m
findDuplicates filterByName thisLocation errorMessage = do findDuplicates filterByName thisLocation errorMessage =
ast' <- asks ast asks ast >>= go . foldr filterByName []
let locations' = foldr filterByName [] ast'
if length locations' > 1 && head locations' == thisLocation
then pure $ error' locations'
else lift mempty
where where
error' locations' = Error go locations' =
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'
} }
@ -530,16 +533,20 @@ uniqueArgumentNamesRule = ArgumentsRule fieldRule directiveRule
-- used, the expected metadata or behavior becomes ambiguous, therefore only one -- used, the expected metadata or behavior becomes ambiguous, therefore only one
-- of each directive is allowed per location. -- of each directive is allowed per location.
uniqueDirectiveNamesRule :: forall m. Rule m uniqueDirectiveNamesRule :: forall m. Rule m
uniqueDirectiveNamesRule = DirectivesRule uniqueDirectiveNamesRule = DirectivesRule $ const $ \directives' -> do
$ const $ lift . filterDuplicates extract "directive" definitions' <- asks $ Schema.directives . schema
let filterNonRepeatable = flip HashSet.member nonRepeatableSet
. getField @"name"
nonRepeatableSet =
HashMap.foldlWithKey foldNonRepeatable HashSet.empty definitions'
lift $ filterDuplicates extract "directive"
$ filter filterNonRepeatable directives'
where where
extract (Full.Directive directiveName _ location') = foldNonRepeatable hashSet directiveName' (Schema.Directive _ _ False _) =
(directiveName, location') HashSet.insert directiveName' hashSet
foldNonRepeatable hashSet _ _ = hashSet
groupSorted :: forall a. (a -> Text) -> [a] -> [[a]] extract (Full.Directive directiveName' _ location') =
groupSorted getName = groupBy equalByName . sortOn getName (directiveName', location')
where
equalByName lhs rhs = getName lhs == getName rhs
filterDuplicates :: forall a filterDuplicates :: forall a
. (a -> (Text, Full.Location)) . (a -> (Text, Full.Location))
@ -549,12 +556,12 @@ filterDuplicates :: forall a
filterDuplicates extract nodeType = Seq.fromList filterDuplicates extract nodeType = Seq.fromList
. fmap makeError . fmap makeError
. filter ((> 1) . length) . filter ((> 1) . length)
. groupSorted getName . NonEmpty.groupAllWith getName
where where
getName = fst . extract getName = fst . extract
makeError directives' = Error makeError directives' = Error
{ message = makeMessage $ head directives' { message = makeMessage $ NonEmpty.head directives'
, locations = snd . extract <$> directives' , locations = snd . extract <$> toList directives'
} }
makeMessage directive = concat makeMessage directive = concat
[ "There can be only one " [ "There can be only one "
@ -833,7 +840,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
@ -854,18 +861,18 @@ knownArgumentNamesRule = ArgumentsRule fieldRule directiveRule
knownDirectiveNamesRule :: Rule m knownDirectiveNamesRule :: Rule m
knownDirectiveNamesRule = DirectivesRule $ const $ \directives' -> do knownDirectiveNamesRule = DirectivesRule $ const $ \directives' -> do
definitions' <- asks $ Schema.directives . schema definitions' <- asks $ Schema.directives . schema
let directiveSet = HashSet.fromList $ fmap directiveName directives' let directiveSet = HashSet.fromList $ fmap (getField @"name") directives'
let definitionSet = HashSet.fromList $ HashMap.keys definitions' definitionSet = HashSet.fromList $ HashMap.keys definitions'
let difference = HashSet.difference directiveSet definitionSet difference = HashSet.difference directiveSet definitionSet
let undefined' = filter (definitionFilter difference) directives' undefined' = filter (definitionFilter difference) directives'
lift $ Seq.fromList $ makeError <$> undefined' lift $ Seq.fromList $ makeError <$> undefined'
where where
definitionFilter :: HashSet Full.Name -> Full.Directive -> Bool
definitionFilter difference = flip HashSet.member difference definitionFilter difference = flip HashSet.member difference
. directiveName . getField @"name"
directiveName (Full.Directive directiveName' _ _) = directiveName' makeError Full.Directive{..} = Error
makeError (Full.Directive directiveName' _ location') = Error { message = errorMessage name
{ message = errorMessage directiveName' , locations = [location]
, locations = [location']
} }
errorMessage directiveName' = concat errorMessage directiveName' = concat
[ "Unknown directive \"@" [ "Unknown directive \"@"
@ -913,7 +920,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]
@ -943,7 +950,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
@ -1411,7 +1418,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

@ -1,15 +1,26 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
module Language.GraphQL.AST.Arbitrary where module Language.GraphQL.AST.Arbitrary
( AnyArgument(..)
, AnyLocation(..)
, AnyName(..)
, AnyNode(..)
, AnyObjectField(..)
, AnyValue(..)
, printArgument
) where
import qualified Language.GraphQL.AST.Document as Doc import qualified Language.GraphQL.AST.Document as Doc
import Test.QuickCheck.Arbitrary (Arbitrary (arbitrary)) 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)
import qualified Data.Text as Text
import Data.Functor ((<&>)) import Data.Functor ((<&>))
newtype AnyPrintableChar = AnyPrintableChar { getAnyPrintableChar :: Char } deriving (Eq, Show) newtype AnyPrintableChar = AnyPrintableChar
{ getAnyPrintableChar :: Char
} deriving (Eq, Show)
alpha :: String alpha :: String
alpha = ['a'..'z'] <> ['A'..'Z'] alpha = ['a'..'z'] <> ['A'..'Z']
@ -20,30 +31,42 @@ num = ['0'..'9']
instance Arbitrary AnyPrintableChar where instance Arbitrary AnyPrintableChar where
arbitrary = AnyPrintableChar <$> elements chars arbitrary = AnyPrintableChar <$> elements chars
where where
chars = alpha <> num <> ['_'] chars = alpha <> num <> ['_']
newtype AnyPrintableText = AnyPrintableText { getAnyPrintableText :: Text } deriving (Eq, Show) newtype AnyPrintableText = AnyPrintableText
{ getAnyPrintableText :: Text
} deriving (Eq, Show)
instance Arbitrary AnyPrintableText where instance Arbitrary AnyPrintableText where
arbitrary = do arbitrary = do
nonEmptyStr <- getNonEmpty <$> (arbitrary :: Gen (NonEmptyList AnyPrintableChar)) nonEmptyStr <- getNonEmpty <$> (arbitrary :: Gen (NonEmptyList AnyPrintableChar))
pure $ AnyPrintableText (pack $ map getAnyPrintableChar nonEmptyStr) pure $ AnyPrintableText
$ Text.pack
$ map getAnyPrintableChar nonEmptyStr
-- https://spec.graphql.org/June2018/#Name -- https://spec.graphql.org/June2018/#Name
newtype AnyName = AnyName { getAnyName :: Text } deriving (Eq, Show) newtype AnyName = AnyName
{ getAnyName :: Text
} deriving (Eq, Show)
instance Arbitrary AnyName where instance Arbitrary AnyName where
arbitrary = do arbitrary = do
firstChar <- elements $ alpha <> ['_'] firstChar <- elements $ alpha <> ['_']
rest <- (arbitrary :: Gen [AnyPrintableChar]) rest <- (arbitrary :: Gen [AnyPrintableChar])
pure $ AnyName (pack $ firstChar : map getAnyPrintableChar rest) pure $ AnyName
$ Text.pack
$ firstChar : map getAnyPrintableChar rest
newtype AnyLocation = AnyLocation { getAnyLocation :: Doc.Location } deriving (Eq, Show) newtype AnyLocation = AnyLocation
{ getAnyLocation :: Doc.Location
} deriving (Eq, Show)
instance Arbitrary AnyLocation where instance Arbitrary AnyLocation where
arbitrary = AnyLocation <$> (Doc.Location <$> arbitrary <*> arbitrary) arbitrary = AnyLocation <$> (Doc.Location <$> arbitrary <*> arbitrary)
newtype AnyNode a = AnyNode { getAnyNode :: Doc.Node a } deriving (Eq, Show) newtype AnyNode a = AnyNode
{ getAnyNode :: Doc.Node a
} deriving (Eq, Show)
instance Arbitrary a => Arbitrary (AnyNode a) where instance Arbitrary a => Arbitrary (AnyNode a) where
arbitrary = do arbitrary = do
@ -51,7 +74,9 @@ instance Arbitrary a => Arbitrary (AnyNode a) where
node' <- flip Doc.Node location' <$> arbitrary node' <- flip Doc.Node location' <$> arbitrary
pure $ AnyNode node' pure $ AnyNode node'
newtype AnyObjectField a = AnyObjectField { getAnyObjectField :: Doc.ObjectField a } deriving (Eq, Show) newtype AnyObjectField a = AnyObjectField
{ getAnyObjectField :: Doc.ObjectField a
} deriving (Eq, Show)
instance Arbitrary a => Arbitrary (AnyObjectField a) where instance Arbitrary a => Arbitrary (AnyObjectField a) where
arbitrary = do arbitrary = do
@ -60,8 +85,9 @@ 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
deriving (Eq, Show) { getAnyValue :: Doc.Value
} deriving (Eq, Show)
instance Arbitrary AnyValue instance Arbitrary AnyValue
where where
@ -88,8 +114,9 @@ instance Arbitrary AnyValue
, Doc.Object <$> objectGen , Doc.Object <$> objectGen
] ]
newtype AnyArgument a = AnyArgument { getAnyArgument :: Doc.Argument } newtype AnyArgument a = AnyArgument
deriving (Eq, Show) { getAnyArgument :: Doc.Argument
} deriving (Eq, Show)
instance Arbitrary a => Arbitrary (AnyArgument a) where instance Arbitrary a => Arbitrary (AnyArgument a) where
arbitrary = do arbitrary = do
@ -99,4 +126,5 @@ instance Arbitrary a => Arbitrary (AnyArgument a) where
pure $ AnyArgument $ Doc.Argument name' (Doc.Node value' location') location' pure $ AnyArgument $ Doc.Argument name' (Doc.Node value' location') location'
printArgument :: AnyArgument AnyValue -> Text printArgument :: AnyArgument AnyValue -> Text
printArgument (AnyArgument (Doc.Argument name' (Doc.Node value' _) _)) = name' <> ": " <> (pack . show) value' printArgument (AnyArgument (Doc.Argument name' (Doc.Node value' _) _)) =
name' <> ": " <> (Text.pack . show) value'

View File

@ -1,5 +1,4 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module Language.GraphQL.AST.EncoderSpec module Language.GraphQL.AST.EncoderSpec
( spec ( spec
) where ) where
@ -7,20 +6,17 @@ module Language.GraphQL.AST.EncoderSpec
import Data.List.NonEmpty (NonEmpty(..)) import Data.List.NonEmpty (NonEmpty(..))
import qualified Language.GraphQL.AST.Document as Full import qualified Language.GraphQL.AST.Document as Full
import Language.GraphQL.AST.Encoder import Language.GraphQL.AST.Encoder
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
describe "value" $ do describe "value" $ do
context "null value" $ do
let testNull formatter = value formatter Full.Null `shouldBe` "null"
it "minified" $ testNull minified
it "pretty" $ testNull pretty
context "minified" $ do context "minified" $ do
it "encodes null" $
value minified Full.Null `shouldBe` "null"
it "escapes \\" $ it "escapes \\" $
value minified (Full.String "\\") `shouldBe` "\"\\\\\"" value minified (Full.String "\\") `shouldBe` "\"\\\\\""
it "escapes double quotes" $ it "escapes double quotes" $
@ -46,113 +42,95 @@ spec = do
it "~" $ value minified (Full.String "\x007E") `shouldBe` "\"~\"" it "~" $ value minified (Full.String "\x007E") `shouldBe` "\"~\""
context "pretty" $ do context "pretty" $ do
it "encodes null" $
value pretty Full.Null `shouldBe` "null"
it "uses strings for short string values" $ it "uses strings for short string values" $
value pretty (Full.String "Short text") `shouldBe` "\"Short text\"" value pretty (Full.String "Short text") `shouldBe` "\"Short text\""
it "uses block strings for text with new lines, with newline symbol" $ it "uses block strings for text with new lines, with newline symbol" $
let expected = [gql| let expected = "\"\"\"\n\
""" \ Line 1\n\
Line 1 \ Line 2\n\
Line 2 \\"\"\""
"""
|]
actual = value pretty $ Full.String "Line 1\nLine 2" actual = value pretty $ Full.String "Line 1\nLine 2"
in actual `shouldBe` expected in actual `shouldBe` expected
it "uses block strings for text with new lines, with CR symbol" $ it "uses block strings for text with new lines, with CR symbol" $
let expected = [gql| let expected = "\"\"\"\n\
""" \ Line 1\n\
Line 1 \ Line 2\n\
Line 2 \\"\"\""
"""
|]
actual = value pretty $ Full.String "Line 1\rLine 2" actual = value pretty $ Full.String "Line 1\rLine 2"
in actual `shouldBe` expected in actual `shouldBe` expected
it "uses block strings for text with new lines, with CR symbol followed by newline" $ it "uses block strings for text with new lines, with CR symbol followed by newline" $
let expected = [gql| let expected = "\"\"\"\n\
""" \ Line 1\n\
Line 1 \ Line 2\n\
Line 2 \\"\"\""
"""
|]
actual = value pretty $ Full.String "Line 1\r\nLine 2" actual = value pretty $ Full.String "Line 1\r\nLine 2"
in actual `shouldBe` expected in actual `shouldBe` expected
it "encodes as one line string if has escaped symbols" $ do it "encodes as one line string if has escaped symbols" $ do
let let genNotAllowedSymbol = oneof
genNotAllowedSymbol = oneof [ choose ('\x0000', '\x0008')
[ choose ('\x0000', '\x0008') , choose ('\x000B', '\x000C')
, choose ('\x000B', '\x000C') , choose ('\x000E', '\x001F')
, choose ('\x000E', '\x001F') , pure '\x007F'
, pure '\x007F' ]
]
forAll genNotAllowedSymbol $ \x -> do forAll genNotAllowedSymbol $ \x -> do
let let rawValue = "Short \n" <> Text.Lazy.cons x "text"
rawValue = "Short \n" <> Text.Lazy.cons x "text" encoded = Text.Lazy.unpack
encoded = value pretty $ value pretty
$ Full.String $ Text.Lazy.toStrict rawValue $ Full.String
shouldStartWith (Text.Lazy.unpack encoded) "\"" $ Text.Lazy.toStrict rawValue
shouldEndWith (Text.Lazy.unpack encoded) "\"" shouldStartWith encoded "\""
shouldNotContain (Text.Lazy.unpack encoded) "\"\"\"" shouldEndWith encoded "\""
shouldNotContain encoded "\"\"\""
it "Hello world" $ it "Hello world" $
let actual = value pretty let actual = value pretty
$ Full.String "Hello,\n World!\n\nYours,\n GraphQL." $ Full.String "Hello,\n World!\n\nYours,\n GraphQL."
expected = [gql| expected = "\"\"\"\n\
""" \ Hello,\n\
Hello, \ World!\n\
World! \\n\
\ Yours,\n\
Yours, \ GraphQL.\n\
GraphQL. \\"\"\""
"""
|]
in actual `shouldBe` expected in actual `shouldBe` expected
it "has only newlines" $ it "has only newlines" $
let actual = value pretty $ Full.String "\n" let actual = value pretty $ Full.String "\n"
expected = [gql| expected = "\"\"\"\n\n\n\"\"\""
"""
"""
|]
in actual `shouldBe` expected in actual `shouldBe` expected
it "has newlines and one symbol at the begining" $ it "has newlines and one symbol at the begining" $
let actual = value pretty $ Full.String "a\n\n" let actual = value pretty $ Full.String "a\n\n"
expected = [gql| expected = "\"\"\"\n\
""" \ a\n\
a \\n\
\\n\
\\"\"\""
"""|]
in actual `shouldBe` expected in actual `shouldBe` expected
it "has newlines and one symbol at the end" $ it "has newlines and one symbol at the end" $
let actual = value pretty $ Full.String "\n\na" let actual = value pretty $ Full.String "\n\na"
expected = [gql| expected = "\"\"\"\n\
""" \\n\
\\n\
\ a\n\
a \\"\"\""
"""
|]
in actual `shouldBe` expected in actual `shouldBe` expected
it "has newlines and one symbol in the middle" $ it "has newlines and one symbol in the middle" $
let actual = value pretty $ Full.String "\na\n" let actual = value pretty $ Full.String "\na\n"
expected = [gql| expected = "\"\"\"\n\
""" \\n\
\ a\n\
a \\n\
\\"\"\""
"""
|]
in actual `shouldBe` expected in actual `shouldBe` expected
it "skip trailing whitespaces" $ it "skip trailing whitespaces" $
let actual = value pretty $ Full.String " Short\ntext " let actual = value pretty $ Full.String " Short\ntext "
expected = [gql| expected = "\"\"\"\n\
""" \ Short\n\
Short \ text\n\
text \\"\"\""
"""
|]
in actual `shouldBe` expected in actual `shouldBe` expected
describe "definition" $ describe "definition" $
@ -164,14 +142,12 @@ spec = do
fieldSelection = pure $ Full.FieldSelection field fieldSelection = pure $ Full.FieldSelection field
operation = Full.DefinitionOperation operation = Full.DefinitionOperation
$ Full.SelectionSet fieldSelection location $ Full.SelectionSet fieldSelection location
expected = Text.Lazy.snoc [gql| expected = "{\n\
{ \ field(message: \"\"\"\n\
field(message: """ \ line1\n\
line1 \ line2\n\
line2 \ \"\"\")\n\
""") \}\n"
}
|] '\n'
actual = definition pretty operation actual = definition pretty operation
in actual `shouldBe` expected in actual `shouldBe` expected
@ -186,12 +162,10 @@ spec = do
mutationType = Full.OperationTypeDefinition Full.Mutation "MutationType" mutationType = Full.OperationTypeDefinition Full.Mutation "MutationType"
operations = queryType :| pure mutationType operations = queryType :| pure mutationType
definition' = Full.SchemaDefinition [] operations definition' = Full.SchemaDefinition [] operations
expected = Text.Lazy.snoc [gql| expected = "schema {\n\
schema { \ query: QueryRootType\n\
query: QueryRootType \ mutation: MutationType\n\
mutation: MutationType \}\n"
}
|] '\n'
actual = typeSystemDefinition pretty definition' actual = typeSystemDefinition pretty definition'
in actual `shouldBe` expected in actual `shouldBe` expected
@ -210,11 +184,9 @@ spec = do
$ Full.InterfaceTypeDefinition mempty "UUID" mempty $ Full.InterfaceTypeDefinition mempty "UUID" mempty
$ pure $ pure
$ Full.FieldDefinition mempty "value" arguments someType mempty $ Full.FieldDefinition mempty "value" arguments someType mempty
expected = [gql| expected = "interface UUID {\n\
interface UUID { \ value(arg: String): String\n\
value(arg: String): String \}"
}
|]
actual = typeSystemDefinition pretty definition' actual = typeSystemDefinition pretty definition'
in actual `shouldBe` expected in actual `shouldBe` expected
@ -222,11 +194,9 @@ spec = do
let definition' = Full.TypeDefinition let definition' = Full.TypeDefinition
$ Full.UnionTypeDefinition mempty "SearchResult" mempty $ Full.UnionTypeDefinition mempty "SearchResult" mempty
$ Full.UnionMemberTypes ["Photo", "Person"] $ Full.UnionMemberTypes ["Photo", "Person"]
expected = [gql| expected = "union SearchResult =\n\
union SearchResult = \ | Photo\n\
| Photo \ | Person"
| Person
|]
actual = typeSystemDefinition pretty definition' actual = typeSystemDefinition pretty definition'
in actual `shouldBe` expected in actual `shouldBe` expected
@ -239,14 +209,12 @@ spec = do
] ]
definition' = Full.TypeDefinition definition' = Full.TypeDefinition
$ Full.EnumTypeDefinition mempty "Direction" mempty values $ Full.EnumTypeDefinition mempty "Direction" mempty values
expected = [gql| expected = "enum Direction {\n\
enum Direction { \ NORTH\n\
NORTH \ EAST\n\
EAST \ SOUTH\n\
SOUTH \ WEST\n\
WEST \}"
}
|]
actual = typeSystemDefinition pretty definition' actual = typeSystemDefinition pretty definition'
in actual `shouldBe` expected in actual `shouldBe` expected
@ -259,11 +227,28 @@ spec = do
] ]
definition' = Full.TypeDefinition definition' = Full.TypeDefinition
$ Full.InputObjectTypeDefinition mempty "ExampleInputObject" mempty fields $ Full.InputObjectTypeDefinition mempty "ExampleInputObject" mempty fields
expected = [gql| expected = "input ExampleInputObject {\n\
input ExampleInputObject { \ a: String\n\
a: String \ b: Int!\n\
b: Int! \}"
}
|]
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 = "@example() on\n\
\ | 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 = "@example() repeatable on\n\
\ | FIELD"
actual = typeSystemDefinition pretty definition'
in actual `shouldBe` expected

View File

@ -1,5 +1,4 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module Language.GraphQL.AST.LexerSpec module Language.GraphQL.AST.LexerSpec
( spec ( spec
) where ) where
@ -7,7 +6,6 @@ module Language.GraphQL.AST.LexerSpec
import Data.Text (Text) import Data.Text (Text)
import Data.Void (Void) import Data.Void (Void)
import Language.GraphQL.AST.Lexer import Language.GraphQL.AST.Lexer
import Language.GraphQL.TH
import Test.Hspec (Spec, context, describe, it) import Test.Hspec (Spec, context, describe, it)
import Test.Hspec.Megaparsec (shouldParse, shouldFailOn, shouldSucceedOn) import Test.Hspec.Megaparsec (shouldParse, shouldFailOn, shouldSucceedOn)
import Text.Megaparsec (ParseErrorBundle, parse) import Text.Megaparsec (ParseErrorBundle, parse)
@ -19,38 +17,39 @@ spec = describe "Lexer" $ do
parse unicodeBOM "" `shouldSucceedOn` "\xfeff" parse unicodeBOM "" `shouldSucceedOn` "\xfeff"
it "lexes strings" $ do it "lexes strings" $ do
parse string "" [gql|"simple"|] `shouldParse` "simple" parse string "" "\"simple\"" `shouldParse` "simple"
parse string "" [gql|" white space "|] `shouldParse` " white space " parse string "" "\" white space \"" `shouldParse` " white space "
parse string "" [gql|"quote \""|] `shouldParse` [gql|quote "|] parse string "" "\"quote \\\"\"" `shouldParse` "quote \""
parse string "" [gql|"escaped \n"|] `shouldParse` "escaped \n" parse string "" "\"escaped \\n\"" `shouldParse` "escaped \n"
parse string "" [gql|"slashes \\ \/"|] `shouldParse` [gql|slashes \ /|] parse string "" "\"slashes \\\\ \\/\"" `shouldParse` "slashes \\ /"
parse string "" [gql|"unicode \u1234\u5678\u90AB\uCDEF"|] parse string "" "\"unicode \\u1234\\u5678\\u90AB\\uCDEF\""
`shouldParse` "unicode ሴ噸邫췯" `shouldParse` "unicode ሴ噸邫췯"
it "lexes block string" $ do it "lexes block string" $ do
parse blockString "" [gql|"""simple"""|] `shouldParse` "simple" parse blockString "" "\"\"\"simple\"\"\"" `shouldParse` "simple"
parse blockString "" [gql|""" white space """|] parse blockString "" "\"\"\" white space \"\"\""
`shouldParse` " white space " `shouldParse` " white space "
parse blockString "" [gql|"""contains " quote"""|] parse blockString "" "\"\"\"contains \" quote\"\"\""
`shouldParse` [gql|contains " quote|] `shouldParse` "contains \" quote"
parse blockString "" [gql|"""contains \""" triplequote"""|] parse blockString "" "\"\"\"contains \\\"\"\" triplequote\"\"\""
`shouldParse` [gql|contains """ triplequote|] `shouldParse` "contains \"\"\" triplequote"
parse blockString "" "\"\"\"multi\nline\"\"\"" `shouldParse` "multi\nline" parse blockString "" "\"\"\"multi\nline\"\"\"" `shouldParse` "multi\nline"
parse blockString "" "\"\"\"multi\rline\r\nnormalized\"\"\"" parse blockString "" "\"\"\"multi\rline\r\nnormalized\"\"\""
`shouldParse` "multi\nline\nnormalized" `shouldParse` "multi\nline\nnormalized"
parse blockString "" "\"\"\"multi\rline\r\nnormalized\"\"\"" parse blockString "" "\"\"\"multi\rline\r\nnormalized\"\"\""
`shouldParse` "multi\nline\nnormalized" `shouldParse` "multi\nline\nnormalized"
parse blockString "" [gql|"""unescaped \n\r\b\t\f\u1234"""|] parse blockString "" "\"\"\"unescaped \\n\\r\\b\\t\\f\\u1234\"\"\""
`shouldParse` [gql|unescaped \n\r\b\t\f\u1234|] `shouldParse` "unescaped \\n\\r\\b\\t\\f\\u1234"
parse blockString "" [gql|"""slashes \\ \/"""|] parse blockString "" "\"\"\"slashes \\\\ \\/\"\"\""
`shouldParse` [gql|slashes \\ \/|] `shouldParse` "slashes \\\\ \\/"
parse blockString "" [gql|""" parse blockString "" "\"\"\"\n\
\\n\
spans \ spans\n\
multiple \ multiple\n\
lines \ lines\n\
\\n\
"""|] `shouldParse` "spans\n multiple\n lines" \\"\"\""
`shouldParse` "spans\n multiple\n lines"
it "lexes numbers" $ do it "lexes numbers" $ do
parse integer "" "4" `shouldParse` (4 :: Int) parse integer "" "4" `shouldParse` (4 :: Int)
@ -84,7 +83,7 @@ spec = describe "Lexer" $ do
context "Implementation tests" $ do context "Implementation tests" $ do
it "lexes empty block strings" $ it "lexes empty block strings" $
parse blockString "" [gql|""""""|] `shouldParse` "" parse blockString "" "\"\"\"\"\"\"" `shouldParse` ""
it "lexes ampersand" $ it "lexes ampersand" $
parse amp "" "&" `shouldParse` "&" parse amp "" "&" `shouldParse` "&"
it "lexes schema extensions" $ it "lexes schema extensions" $

View File

@ -1,18 +1,20 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module Language.GraphQL.AST.ParserSpec module Language.GraphQL.AST.ParserSpec
( spec ( spec
) where ) where
import Data.List.NonEmpty (NonEmpty(..)) import Data.List.NonEmpty (NonEmpty(..))
import Data.Text (Text)
import qualified Data.Text as Text import qualified Data.Text as Text
import Language.GraphQL.AST.Document import Language.GraphQL.AST.Document
import qualified Language.GraphQL.AST.DirectiveLocation as DirLoc import qualified Language.GraphQL.AST.DirectiveLocation as DirLoc
import Language.GraphQL.AST.Parser import Language.GraphQL.AST.Parser
import Language.GraphQL.TH
import Test.Hspec (Spec, describe, it, context) import Test.Hspec (Spec, describe, it, context)
import Test.Hspec.Megaparsec (shouldParse, shouldFailOn, shouldSucceedOn) import Test.Hspec.Megaparsec
( 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
@ -23,182 +25,154 @@ spec = describe "Parser" $ do
parse document "" `shouldSucceedOn` "\xfeff{foo}" parse document "" `shouldSucceedOn` "\xfeff{foo}"
context "Arguments" $ do context "Arguments" $ do
it "accepts block strings as argument" $ it "accepts block strings as argument" $
parse document "" `shouldSucceedOn` [gql|{ parse document "" `shouldSucceedOn`
hello(text: """Argument""") "{ hello(text: \"\"\"Argument\"\"\") }"
}|]
it "accepts strings as argument" $ it "accepts strings as argument" $
parse document "" `shouldSucceedOn` [gql|{ parse document "" `shouldSucceedOn` "{ hello(text: \"Argument\") }"
hello(text: "Argument")
}|]
it "accepts int as argument1" $ it "accepts int as argument" $
parse document "" `shouldSucceedOn` [gql|{ parse document "" `shouldSucceedOn` "{ user(id: 4) }"
user(id: 4)
}|]
it "accepts boolean as argument" $ it "accepts boolean as argument" $
parse document "" `shouldSucceedOn` [gql|{ parse document "" `shouldSucceedOn`
hello(flag: true) { field1 } "{ hello(flag: true) { field1 } }"
}|]
it "accepts float as argument" $ it "accepts float as argument" $
parse document "" `shouldSucceedOn` [gql|{ parse document "" `shouldSucceedOn`
body(height: 172.5) { height } "{ body(height: 172.5) { height } }"
}|]
it "accepts empty list as argument" $ it "accepts empty list as argument" $
parse document "" `shouldSucceedOn` [gql|{ parse document "" `shouldSucceedOn` "{ query(list: []) { field1 } }"
query(list: []) { field1 }
}|]
it "accepts two required arguments" $ it "accepts two required arguments" $
parse document "" `shouldSucceedOn` [gql| parse document "" `shouldSucceedOn`
mutation auth($username: String!, $password: String!){ "mutation auth($username: String!, $password: String!) { test }"
test
}|]
it "accepts two string arguments" $ it "accepts two string arguments" $
parse document "" `shouldSucceedOn` [gql| parse document "" `shouldSucceedOn`
mutation auth{ "mutation auth { test(username: \"username\", password: \"password\") }"
test(username: "username", password: "password")
}|]
it "accepts two block string arguments" $ it "accepts two block string arguments" $
parse document "" `shouldSucceedOn` [gql| let given = "mutation auth {\n\
mutation auth{ \ test(username: \"\"\"username\"\"\", password: \"\"\"password\"\"\")\n\
test(username: """username""", password: """password""") \}"
}|] in parse document "" `shouldSucceedOn` given
it "accepts any arguments" $ mapSize (const 10) $ property $ \xs -> it "fails to parse an empty argument list in parens" $
let parse document "" `shouldFailOn` "{ test() }"
query' :: Text
arguments = map printArgument $ getNonEmpty (xs :: NonEmptyList (AnyArgument AnyValue)) it "accepts any arguments" $ mapSize (const 10) $ property $ \xs ->
query' = "query(" <> Text.intercalate ", " arguments <> ")" in let arguments' = map printArgument
parse document "" `shouldSucceedOn` ("{ " <> query' <> " }") $ getNonEmpty (xs :: NonEmptyList (AnyArgument AnyValue))
query' = "query(" <> Text.intercalate ", " arguments' <> ")"
in parse document "" `shouldSucceedOn` ("{ " <> query' <> " }")
it "parses minimal schema definition" $ it "parses minimal schema definition" $
parse document "" `shouldSucceedOn` [gql|schema { query: Query }|] parse document "" `shouldSucceedOn` "schema { query: Query }"
it "parses minimal scalar definition" $ it "parses minimal scalar definition" $
parse document "" `shouldSucceedOn` [gql|scalar Time|] parse document "" `shouldSucceedOn` "scalar Time"
it "parses ImplementsInterfaces" $ it "parses ImplementsInterfaces" $
parse document "" `shouldSucceedOn` [gql| parse document "" `shouldSucceedOn`
type Person implements NamedEntity & ValuedEntity { "type Person implements NamedEntity & ValuedEntity {\n\
name: String \ name: String\n\
} \}"
|]
it "parses a type without ImplementsInterfaces" $ it "parses a type without ImplementsInterfaces" $
parse document "" `shouldSucceedOn` [gql| parse document "" `shouldSucceedOn`
type Person { "type Person {\n\
name: String \ name: String\n\
} \}"
|]
it "parses ArgumentsDefinition in an ObjectDefinition" $ it "parses ArgumentsDefinition in an ObjectDefinition" $
parse document "" `shouldSucceedOn` [gql| parse document "" `shouldSucceedOn`
type Person { "type Person {\n\
name(first: String, last: String): String \ name(first: String, last: String): String\n\
} \}"
|]
it "parses minimal union type definition" $ it "parses minimal union type definition" $
parse document "" `shouldSucceedOn` [gql| parse document "" `shouldSucceedOn`
union SearchResult = Photo | Person "union SearchResult = Photo | Person"
|]
it "parses minimal interface type definition" $ it "parses minimal interface type definition" $
parse document "" `shouldSucceedOn` [gql| parse document "" `shouldSucceedOn`
interface NamedEntity { "interface NamedEntity {\n\
name: String \ name: String\n\
} \}"
|]
it "parses minimal enum type definition" $ it "parses minimal enum type definition" $
parse document "" `shouldSucceedOn` [gql| parse document "" `shouldSucceedOn`
enum Direction { "enum Direction {\n\
NORTH \ NORTH\n\
EAST \ EAST\n\
SOUTH \ SOUTH\n\
WEST \ WEST\n\
} \}"
|]
it "parses minimal input object type definition" $ it "parses minimal input object type definition" $
parse document "" `shouldSucceedOn` [gql| parse document "" `shouldSucceedOn`
input Point2D { "input Point2D {\n\
x: Float \ x: Float\n\
y: Float \ y: Float\n\
} \}"
|]
it "parses minimal input enum definition with an optional pipe" $ it "parses minimal input enum definition with an optional pipe" $
parse document "" `shouldSucceedOn` [gql| parse document "" `shouldSucceedOn`
directive @example on "directive @example on\n\
| FIELD \ | FIELD\n\
| FRAGMENT_SPREAD \ | FRAGMENT_SPREAD"
|]
it "parses two minimal directive definitions" $ it "parses two minimal directive definitions" $
let directive nm loc = let directive name' loc = TypeSystemDefinition
TypeSystemDefinition $ DirectiveDefinition
(DirectiveDefinition (Description Nothing)
(Description Nothing) name'
nm (ArgumentsDefinition [])
(ArgumentsDefinition []) False
(loc :| [])) (loc :| [])
example1 = example1 = directive "example1"
directive "example1" (DirLoc.TypeSystemDirectiveLocation DirLoc.FieldDefinition)
(DirLoc.TypeSystemDirectiveLocation DirLoc.FieldDefinition) (Location {line = 1, column = 1})
(Location {line = 1, column = 1}) example2 = directive "example2"
example2 = (DirLoc.ExecutableDirectiveLocation DirLoc.Field)
directive "example2" (Location {line = 2, column = 1})
(DirLoc.ExecutableDirectiveLocation DirLoc.Field) testSchemaExtension = example1 :| [example2]
(Location {line = 2, column = 1}) query = Text.unlines
testSchemaExtension = example1 :| [ example2 ] [ "directive @example1 on FIELD_DEFINITION"
query = [gql| , "directive @example2 on FIELD"
directive @example1 on FIELD_DEFINITION ]
directive @example2 on FIELD
|]
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 directive nm loc args = let argumentValue = Just
TypeSystemDefinition $ Node (ConstList [])
(DirectiveDefinition $ Location{ line = 1, column = 33 }
(Description Nothing) loc = DirLoc.TypeSystemDirectiveLocation DirLoc.FieldDefinition
nm argumentValueDefinition = InputValueDefinition
(ArgumentsDefinition (Description Nothing)
[ InputValueDefinition "foo"
(Description Nothing) (TypeList (TypeNamed "String"))
argName argumentValue
argType []
argValue definition = DirectiveDefinition
[] (Description Nothing)
| (argName, argType, argValue) <- args]) "test"
(loc :| [])) (ArgumentsDefinition [argumentValueDefinition])
defn = False
directive "test" (loc :| [])
(DirLoc.TypeSystemDirectiveLocation DirLoc.FieldDefinition) directive = TypeSystemDefinition definition
[("foo", $ Location{ line = 1, column = 1 }
TypeList (TypeNamed "String"), query = "directive @test(foo: [String] = []) on FIELD_DEFINITION"
Just in parse document "" query `shouldParse` (directive :| [])
$ Node (ConstList [])
$ Location {line = 1, column = 33})]
(Location {line = 1, column = 1})
query = [gql|directive @test(foo: [String] = []) on FIELD_DEFINITION|]
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` "extend schema @newDirective"
extend schema @newDirective
|]
it "parses schema extension with an operation type definition" $ it "parses schema extension with an operation type definition" $
parse document "" `shouldSucceedOn` [gql|extend schema { query: Query }|] parse document "" `shouldSucceedOn` "extend schema { query: Query }"
it "parses schema extension with an operation type and directive" $ it "parses schema extension with an operation type and directive" $
let newDirective = Directive "newDirective" [] $ Location 1 15 let newDirective = Directive "newDirective" [] $ Location 1 15
@ -207,45 +181,42 @@ spec = describe "Parser" $ do
$ OperationTypeDefinition Query "Query" :| [] $ OperationTypeDefinition Query "Query" :| []
testSchemaExtension = TypeSystemExtension schemaExtension testSchemaExtension = TypeSystemExtension schemaExtension
$ Location 1 1 $ Location 1 1
query = [gql|extend schema @newDirective { query: Query }|] query = "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 = "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`
extend type Story { "extend type Story { isHiddenLocally: Boolean }"
isHiddenLocally: Boolean
}
|]
it "rejects variables in DefaultValue" $ it "rejects variables in DefaultValue" $
parse document "" `shouldFailOn` [gql| parse document "" `shouldFailOn`
query ($book: String = "Zarathustra", $author: String = $book) { "query ($book: String = \"Zarathustra\", $author: String = $book) {\n\
title \ title\n\
} \}"
|]
it "rejects empty selection set" $ it "rejects empty selection set" $
parse document "" `shouldFailOn` [gql| parse document "" `shouldFailOn` "query { innerField {} }"
query {
innerField {}
}
|]
it "parses documents beginning with a comment" $ it "parses documents beginning with a comment" $
parse document "" `shouldSucceedOn` [gql| parse document "" `shouldSucceedOn`
""" "\"\"\"\n\
Query \Query\n\
""" \\"\"\"\n\
type Query { \type Query {\n\
queryField: String \ queryField: String\n\
} \}"
|]
it "parses subscriptions" $ it "parses subscriptions" $
parse document "" `shouldSucceedOn` [gql| parse document "" `shouldSucceedOn`
subscription NewMessages { "subscription NewMessages {\n\
newMessage(roomId: 123) { \ newMessage(roomId: 123) {\n\
sender \ sender\n\
} \ }\n\
} \}"
|]

View File

@ -5,9 +5,7 @@
{-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE LambdaCase #-} {-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module Language.GraphQL.ExecuteSpec module Language.GraphQL.ExecuteSpec
( spec ( spec
@ -23,7 +21,6 @@ import Language.GraphQL.AST (Document, Location(..), Name)
import Language.GraphQL.AST.Parser (document) import Language.GraphQL.AST.Parser (document)
import Language.GraphQL.Error import Language.GraphQL.Error
import Language.GraphQL.Execute (execute) import Language.GraphQL.Execute (execute)
import Language.GraphQL.TH
import qualified Language.GraphQL.Type.Schema as Schema import qualified Language.GraphQL.Type.Schema as Schema
import qualified Language.GraphQL.Type as Type import qualified Language.GraphQL.Type as Type
import Language.GraphQL.Type import Language.GraphQL.Type
@ -269,15 +266,15 @@ spec :: Spec
spec = spec =
describe "execute" $ do describe "execute" $ do
it "rejects recursive fragments" $ it "rejects recursive fragments" $
let sourceQuery = [gql| let sourceQuery = "\
{ \{\n\
...cyclicFragment \ ...cyclicFragment\n\
} \}\n\
\\n\
fragment cyclicFragment on Query { \fragment cyclicFragment on Query {\n\
...cyclicFragment \ ...cyclicFragment\n\
} \}\
|] \"
expected = Response (Object mempty) mempty expected = Response (Object mempty) mempty
in sourceQuery `shouldResolveTo` expected in sourceQuery `shouldResolveTo` expected

View File

@ -0,0 +1,24 @@
{- 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

File diff suppressed because it is too large Load Diff