Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
21 changes: 10 additions & 11 deletions graphql-api.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
--
-- see: https://github.com/sol/hpack
--
-- hash: 6db006b020fe198ac64b8a50f8335017251389b7c34dfc553675e38eb001a428
-- hash: e921bbdc9931b5b0b16603d36a3252522602c736862259ef71abdecf046541e2

name: graphql-api
version: 0.3.0
Expand Down Expand Up @@ -125,7 +125,7 @@ test-suite graphql-api-doctests

test-suite graphql-api-tests
type: exitcode-stdio-1.0
main-is: Spec.hs
main-is: Main.hs
hs-source-dirs:
tests
default-extensions: NoImplicitPrelude OverloadedStrings RecordWildCards TypeApplications
Expand All @@ -142,19 +142,18 @@ test-suite graphql-api-tests
, hspec
, protolude >=0.2.1
, raw-strings-qq
, tasty
, tasty-hspec
, transformers
other-modules:
ASTTests
EndToEndTests
ASTSpec
EndToEndSpec
EnumTests
ExampleSchema
OrderedMapTests
ResolverTests
SchemaTests
ValidationTests
ValueTests
OrderedMapSpec
ResolverSpec
SchemaSpec
Spec
ValidationSpec
ValueSpec
Paths_graphql_api
default-language: Haskell2010

Expand Down
4 changes: 1 addition & 3 deletions package.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,7 @@ executables:

tests:
graphql-api-tests:
main: Spec.hs
main: Main.hs
source-dirs: tests
dependencies:
- aeson
Expand All @@ -71,8 +71,6 @@ tests:
- hspec
- QuickCheck
- raw-strings-qq
- tasty
- tasty-hspec
- directory

graphql-api-doctests:
Expand Down
9 changes: 4 additions & 5 deletions tests/ASTTests.hs → tests/ASTSpec.hs
Original file line number Diff line number Diff line change
@@ -1,16 +1,15 @@
{-# LANGUAGE QuasiQuotes #-}

-- | Tests for AST, including parser and encoder.
module ASTTests (tests) where
module ASTSpec (spec) where

import Protolude

import Data.Attoparsec.Text (parseOnly)
import Text.RawString.QQ (r)
import Test.Hspec.QuickCheck (prop)
import Test.QuickCheck (arbitrary, forAll, resize)
import Test.Tasty (TestTree)
import Test.Tasty.Hspec (testSpec, describe, it, shouldBe)
import Test.Hspec

import GraphQL.Value (String(..))
import GraphQL.Internal.Name (Name)
Expand All @@ -27,8 +26,8 @@ dog = "dog"
someName :: Name
someName = "name"

tests :: IO TestTree
tests = testSpec "AST" $ do
spec :: Spec
spec = describe "AST" $ do
describe "Parser and encoder" $ do
it "roundtrips on minified documents" $ do
let actual = Encoder.queryDocument <$> parseOnly Parser.queryDocument kitchenSink
Expand Down
9 changes: 4 additions & 5 deletions tests/EndToEndTests.hs → tests/EndToEndSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@
--
-- These tests function both as examples of how to use the API, as well as
-- sanity checks on our reasoning.
module EndToEndTests (tests) where
module EndToEndSpec (spec) where

import Protolude

Expand All @@ -17,8 +17,7 @@ import GraphQL.API (Object, Field, List, Argument, (:>), Defaultable(..), HasAnn
import GraphQL.Internal.Syntax.AST (Variable(..))
import GraphQL.Resolver ((:<>)(..), Handler, unionValue)
import GraphQL.Value (ToValue(..), FromValue(..), makeName)
import Test.Tasty (TestTree)
import Test.Tasty.Hspec (testSpec, describe, it, shouldBe)
import Test.Hspec
import Text.RawString.QQ (r)

import ExampleSchema
Expand Down Expand Up @@ -135,8 +134,8 @@ jml :: ServerHuman
jml = ServerHuman "jml"


tests :: IO TestTree
tests = testSpec "End-to-end tests" $ do
spec :: Spec
spec = describe "End-to-end tests" $ do
describe "interpretAnonymousQuery" $ do
it "Handles the simplest possible valid query" $ do
let query = [r|{
Expand Down
10 changes: 10 additions & 0 deletions tests/Main.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
module Main where

import Protolude

import Test.Hspec
import qualified Spec (spec)

main :: IO ()
main = do
hspec Spec.spec
9 changes: 4 additions & 5 deletions tests/OrderedMapTests.hs → tests/OrderedMapSpec.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,10 @@
module OrderedMapTests (tests) where
module OrderedMapSpec (spec) where

import Protolude

import Test.Hspec.QuickCheck (prop)
import Test.QuickCheck (Gen, arbitrary, forAll)
import Test.Tasty (TestTree)
import Test.Tasty.Hspec (testSpec, describe, it, shouldBe)
import Test.Hspec

import qualified Data.Map as Map
import GraphQL.Internal.OrderedMap (OrderedMap)
Expand All @@ -15,8 +14,8 @@ import qualified GraphQL.Internal.OrderedMap as OrderedMap
orderedMaps :: Gen (OrderedMap Int Int)
orderedMaps = arbitrary

tests :: IO TestTree
tests = testSpec "OrderedMap" $ do
spec :: Spec
spec = describe "OrderedMap" $ do
describe "Integrity" $ do
prop "fromList . toList == id" $ do
forAll orderedMaps (\x -> OrderedMap.orderedMap (OrderedMap.toList x) == Just x)
Expand Down
9 changes: 4 additions & 5 deletions tests/ResolverTests.hs → tests/ResolverSpec.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,11 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
module ResolverTests (tests) where
module ResolverSpec (spec) where

import Protolude hiding (Enum)

import Test.Tasty (TestTree)
import Test.Tasty.Hspec (testSpec, describe, it, shouldBe)
import Test.Hspec

import Data.Aeson (encode)
import GraphQL
Expand Down Expand Up @@ -74,8 +73,8 @@ enumHandler :: Handler IO EnumQuery
enumHandler = pure $ pure NormalFile
-- /Enum test

tests :: IO TestTree
tests = testSpec "TypeAPI" $ do
spec :: Spec
spec = describe "TypeAPI" $ do
describe "tTest" $ do
it "works in a simple case" $ do
Right (Success object) <- runExceptT (interpretAnonymousQuery @T tHandler "{ t(x: 12) }")
Expand Down
11 changes: 5 additions & 6 deletions tests/SchemaTests.hs → tests/SchemaSpec.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,10 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
module SchemaTests (tests) where
module SchemaSpec (spec) where

import Protolude hiding (Down, Enum)

import Test.Tasty (TestTree)
import Test.Tasty.Hspec (testSpec, describe, it, shouldBe)
import Test.Hspec

import GraphQL.API
( Field
Expand Down Expand Up @@ -45,8 +44,8 @@ import GraphQL.Internal.Schema
)
import ExampleSchema

tests :: IO TestTree
tests = testSpec "Type" $ do
spec :: Spec
spec = describe "Type" $ do
describe "Field" $
it "encodes correctly" $ do
getFieldDefinition @(Field "hello" Int) `shouldBe` Right (FieldDefinition "hello" [] (TypeNonNull (NonNullTypeNamed (BuiltinType GInt))))
Expand Down Expand Up @@ -130,4 +129,4 @@ tests = testSpec "Type" $ do
ListType (
TypeNonNull (
NonNullTypeNamed typeDefinitionScalar
)))))))
)))))))
32 changes: 1 addition & 31 deletions tests/Spec.hs
Original file line number Diff line number Diff line change
@@ -1,31 +1 @@
module Main
( main
) where

import Protolude

import Test.Tasty (defaultMain, testGroup)

import qualified ASTTests
import qualified EndToEndTests
import qualified OrderedMapTests
import qualified ResolverTests
import qualified SchemaTests
import qualified ValidationTests
import qualified ValueTests
import qualified EnumTests ()

main :: IO ()
main = do
t <- sequence tests
defaultMain . testGroup "GraphQL API" $ t
where
tests =
[ ASTTests.tests
, EndToEndTests.tests
, OrderedMapTests.tests
, ResolverTests.tests
, SchemaTests.tests
, ValidationTests.tests
, ValueTests.tests
]
{-# OPTIONS_GHC -F -pgmF hspec-discover -optF --module-name=Spec #-}
9 changes: 4 additions & 5 deletions tests/ValidationTests.hs → tests/ValidationSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,14 +2,13 @@
{-# LANGUAGE DataKinds #-}

-- | Tests for query validation.
module ValidationTests (tests) where
module ValidationSpec (spec) where

import Protolude

import Test.Hspec.QuickCheck (prop)
import Test.QuickCheck ((===))
import Test.Tasty (TestTree)
import Test.Tasty.Hspec (testSpec, describe, it, shouldBe)
import Test.Hspec
import qualified Data.Set as Set

import GraphQL.Internal.Name (Name)
Expand All @@ -36,8 +35,8 @@ dog = "dog"
schema :: Schema
schema = emptySchema

tests :: IO TestTree
tests = testSpec "Validation" $ do
spec :: Spec
spec = describe "Validation" $ do
describe "getErrors" $ do
it "Treats simple queries as valid" $ do
let doc = AST.QueryDocument
Expand Down
9 changes: 4 additions & 5 deletions tests/ValueTests.hs → tests/ValueSpec.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,11 @@
{-# LANGUAGE DeriveGeneric #-}
module ValueTests (tests) where
module ValueSpec (spec) where

import Protolude

import Test.Hspec.QuickCheck (prop)
import Test.QuickCheck (forAll)
import Test.Tasty (TestTree)
import Test.Tasty.Hspec (testSpec, describe, it, shouldBe, shouldSatisfy)
import Test.Hspec

import qualified GraphQL.Internal.Syntax.AST as AST
import GraphQL.Internal.Arbitrary (arbitraryText, arbitraryNonEmpty)
Expand All @@ -31,8 +30,8 @@ data Resource = Resource

instance FromValue Resource

tests :: IO TestTree
tests = testSpec "Value" $ do
spec :: Spec
spec = describe "Value" $ do
describe "unionObject" $ do
it "returns empty on empty list" $ do
unionObjects [] `shouldBe` (objectFromList [] :: Maybe Object)
Expand Down