Compare commits

..

No commits in common. "v1.4.0.0" and "v1.3.0.0" have entirely different histories.

24 changed files with 884 additions and 842 deletions

View File

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

View File

@ -9,14 +9,28 @@ on:
jobs:
audit:
runs-on: buildenv
runs-on: haskell
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
- run: hlint -- src tests
- name: Install dependencies
run: |
cabal update
cabal install hlint "--constraint=hlint ==3.8"
- run: cabal exec hlint -- src tests
test:
runs-on: buildenv
runs-on: haskell
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
- name: Install dependencies
run: cabal update
@ -25,8 +39,13 @@ jobs:
- run: cabal test --test-show-details=streaming
doc:
runs-on: buildenv
runs-on: haskell
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
- name: Install dependencies
run: cabal update

View File

@ -7,11 +7,17 @@ on:
jobs:
release:
runs-on: buildenv
runs-on: haskell
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
- name: Upload a candidate
env:
HACKAGE_PASSWORD: ${{ secrets.HACKAGE_PASSWORD }}
run: |
cabal sdist | awk -f .gitea/deploy.awk
cabal sdist
cabal upload --username belka --password ${HACKAGE_PASSWORD}

View File

@ -6,20 +6,6 @@ The format is based on
and this project adheres to
[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
### Changed
- Remove deprecated `runCollectErrs`, `Resolution`, `CollectErrsT` from the
@ -538,7 +524,6 @@ and this project adheres to
### Added
- 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.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

View File

@ -1,7 +1,7 @@
cabal-version: 3.0
cabal-version: 2.4
name: graphql
version: 1.4.0.0
version: 1.3.0.0
synopsis: Haskell GraphQL implementation
description: Haskell <https://spec.graphql.org/June2018/ GraphQL> implementation.
category: Language
@ -21,7 +21,8 @@ extra-source-files:
CHANGELOG.md
README.md
tested-with:
GHC == 9.8.2
GHC == 9.4.7,
GHC == 9.6.3
source-repository head
type: git
@ -57,7 +58,7 @@ library
ghc-options: -Wall
build-depends:
base >= 4.15 && < 5,
base >= 4.7 && < 5,
conduit ^>= 1.3.4,
containers >= 0.6 && < 0.8,
exceptions ^>= 0.10.4,
@ -84,7 +85,6 @@ test-suite graphql-test
Language.GraphQL.Execute.CoerceSpec
Language.GraphQL.Execute.OrderedMapSpec
Language.GraphQL.ExecuteSpec
Language.GraphQL.THSpec
Language.GraphQL.Type.OutSpec
Language.GraphQL.Validate.RulesSpec
Schemas.HeroSchema

View File

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

View File

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

View File

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

View File

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

View File

@ -12,30 +12,20 @@ import Language.Haskell.TH (Exp(..), Lit(..))
stripIndentation :: String -> String
stripIndentation code = reverse
$ dropWhile isLineBreak
$ dropNewlines
$ reverse
$ unlines
$ indent spaces <$> lines' withoutLeadingNewlines
$ indent spaces <$> lines withoutLeadingNewlines
where
indent 0 xs = xs
indent count (' ' : xs) = indent (count - 1) xs
indent _ xs = xs
withoutLeadingNewlines = dropWhile isLineBreak code
withoutLeadingNewlines = dropNewlines code
dropNewlines = dropWhile $ flip any ['\n', '\r'] . (==)
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
-- removed from each line of the string.
{-# DEPRECATED gql "Use Language.GraphQL.Class.gql from graphql-spice instead" #-}
gql :: QuasiQuoter
gql = QuasiQuoter
{ quoteExp = pure . LitE . StringL . stripIndentation

View File

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

View File

@ -48,11 +48,7 @@ data Type m
deriving Eq
-- | Directive definition.
--
-- 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
data Directive = Directive (Maybe Text) [DirectiveLocation] In.Arguments
-- | Directive definitions.
type Directives = HashMap Full.Name Directive

View File

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

View File

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

View File

@ -50,15 +50,14 @@ import Control.Monad.Trans.Class (MonadTrans(..))
import Control.Monad.Trans.Reader (ReaderT(..), ask, asks, mapReaderT)
import Control.Monad.Trans.State (StateT, evalStateT, gets, modify)
import Data.Bifunctor (first)
import Data.Foldable (Foldable(..), find)
import Data.Foldable (find, fold, foldl', toList)
import qualified Data.HashMap.Strict as HashMap
import Data.HashMap.Strict (HashMap)
import Data.HashSet (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.List.NonEmpty (NonEmpty(..))
import qualified Data.List.NonEmpty as NonEmpty
import Data.Ord (comparing)
import Data.Sequence (Seq(..), (|>))
import qualified Data.Sequence as Seq
@ -254,16 +253,14 @@ findDuplicates :: (Full.Definition -> [Full.Location] -> [Full.Location])
-> Full.Location
-> String
-> RuleT m
findDuplicates filterByName thisLocation errorMessage =
asks ast >>= go . foldr filterByName []
findDuplicates filterByName thisLocation errorMessage = do
ast' <- asks ast
let locations' = foldr filterByName [] ast'
if length locations' > 1 && head locations' == thisLocation
then pure $ error' locations'
else lift mempty
where
go locations' =
case locations' of
headLocation : otherLocations -- length locations' > 1
| not $ null otherLocations
, headLocation == thisLocation -> pure $ makeError locations'
_ -> lift mempty
makeError locations' = Error
error' locations' = Error
{ message = errorMessage
, locations = locations'
}
@ -533,20 +530,16 @@ uniqueArgumentNamesRule = ArgumentsRule fieldRule directiveRule
-- used, the expected metadata or behavior becomes ambiguous, therefore only one
-- of each directive is allowed per location.
uniqueDirectiveNamesRule :: forall m. Rule m
uniqueDirectiveNamesRule = DirectivesRule $ const $ \directives' -> do
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'
uniqueDirectiveNamesRule = DirectivesRule
$ const $ lift . filterDuplicates extract "directive"
where
foldNonRepeatable hashSet directiveName' (Schema.Directive _ _ False _) =
HashSet.insert directiveName' hashSet
foldNonRepeatable hashSet _ _ = hashSet
extract (Full.Directive directiveName' _ location') =
(directiveName', location')
extract (Full.Directive 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
. (a -> (Text, Full.Location))
@ -556,12 +549,12 @@ filterDuplicates :: forall a
filterDuplicates extract nodeType = Seq.fromList
. fmap makeError
. filter ((> 1) . length)
. NonEmpty.groupAllWith getName
. groupSorted getName
where
getName = fst . extract
makeError directives' = Error
{ message = makeMessage $ NonEmpty.head directives'
, locations = snd . extract <$> toList directives'
{ message = makeMessage $ head directives'
, locations = snd . extract <$> directives'
}
makeMessage directive = concat
[ "There can be only one "
@ -840,7 +833,7 @@ knownArgumentNamesRule = ArgumentsRule fieldRule directiveRule
. Schema.directives . schema
Full.Argument argumentName _ location' <- lift $ Seq.fromList arguments
case available of
Just (Schema.Directive _ definitions _ _)
Just (Schema.Directive _ _ definitions)
| not $ HashMap.member argumentName definitions ->
pure $ makeError argumentName directiveName location'
_ -> lift mempty
@ -861,18 +854,18 @@ knownArgumentNamesRule = ArgumentsRule fieldRule directiveRule
knownDirectiveNamesRule :: Rule m
knownDirectiveNamesRule = DirectivesRule $ const $ \directives' -> do
definitions' <- asks $ Schema.directives . schema
let directiveSet = HashSet.fromList $ fmap (getField @"name") directives'
definitionSet = HashSet.fromList $ HashMap.keys definitions'
difference = HashSet.difference directiveSet definitionSet
undefined' = filter (definitionFilter difference) directives'
let directiveSet = HashSet.fromList $ fmap directiveName directives'
let definitionSet = HashSet.fromList $ HashMap.keys definitions'
let difference = HashSet.difference directiveSet definitionSet
let undefined' = filter (definitionFilter difference) directives'
lift $ Seq.fromList $ makeError <$> undefined'
where
definitionFilter :: HashSet Full.Name -> Full.Directive -> Bool
definitionFilter difference = flip HashSet.member difference
. getField @"name"
makeError Full.Directive{..} = Error
{ message = errorMessage name
, locations = [location]
. directiveName
directiveName (Full.Directive directiveName' _ _) = directiveName'
makeError (Full.Directive directiveName' _ location') = Error
{ message = errorMessage directiveName'
, locations = [location']
}
errorMessage directiveName' = concat
[ "Unknown directive \"@"
@ -920,7 +913,7 @@ directivesInValidLocationsRule = DirectivesRule directivesRule
maybeDefinition <- asks
$ HashMap.lookup directiveName . Schema.directives . schema
case maybeDefinition of
Just (Schema.Directive _ _ _ allowedLocations)
Just (Schema.Directive _ allowedLocations _)
| directiveLocation `notElem` allowedLocations -> pure $ Error
{ message = errorMessage directiveName directiveLocation
, locations = [location]
@ -950,7 +943,7 @@ providedRequiredArgumentsRule = ArgumentsRule fieldRule directiveRule
available <- asks
$ HashMap.lookup directiveName . Schema.directives . schema
case available of
Just (Schema.Directive _ definitions _ _) ->
Just (Schema.Directive _ _ definitions) ->
let forEach = go (directiveMessage directiveName) arguments location'
in lift $ HashMap.foldrWithKey forEach Seq.empty definitions
_ -> lift mempty
@ -1418,7 +1411,7 @@ variablesInAllowedPositionRule = OperationDefinitionRule $ \case
let Full.Directive directiveName arguments _ = directive
directiveDefinitions <- lift $ asks $ Schema.directives . schema
case HashMap.lookup directiveName directiveDefinitions of
Just (Schema.Directive _ directiveArguments _ _) ->
Just (Schema.Directive _ _ directiveArguments) ->
mapArguments variables directiveArguments arguments
Nothing -> pure mempty
mapArguments variables argumentTypes = fmap fold

View File

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

View File

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

View File

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

View File

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

View File

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

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

File diff suppressed because it is too large Load Diff