Skip to content

Commit

Permalink
test: first solve
Browse files Browse the repository at this point in the history
  • Loading branch information
theobat committed Jun 21, 2018
1 parent 112c494 commit 1c1393d
Show file tree
Hide file tree
Showing 3 changed files with 11 additions and 6 deletions.
5 changes: 2 additions & 3 deletions graphql-api.cabal
@@ -1,8 +1,8 @@
-- This file has been generated from package.yaml by hpack version 0.20.0.
-- This file has been generated from package.yaml by hpack version 0.28.2.
--
-- see: https://github.com/sol/hpack
--
-- hash: 6a38b887cec0d4a157469f5d73041fd16cb286d8f445f4e213c6f08965dbc563
-- hash: 6db006b020fe198ac64b8a50f8335017251389b7c34dfc553675e38eb001a428

name: graphql-api
version: 0.3.0
Expand All @@ -23,7 +23,6 @@ license: Apache
license-file: LICENSE.Apache-2.0
build-type: Simple
cabal-version: >= 1.10

extra-source-files:
CHANGELOG.rst

Expand Down
4 changes: 4 additions & 0 deletions src/GraphQL/Internal/Schema.hs
Expand Up @@ -37,6 +37,7 @@ module GraphQL.Internal.Schema
-- * The schema
, Schema
, makeSchema
, emptySchema
, lookupType
) where

Expand All @@ -59,6 +60,9 @@ newtype Schema = Schema (Map Name TypeDefinition) deriving (Eq, Ord, Show)
makeSchema :: ObjectTypeDefinition -> Schema
makeSchema = Schema . getDefinedTypes

emptySchema :: Schema
emptySchema = Schema (Map.empty :: (Map Name TypeDefinition))

-- | Find the type with the given name in the schema.
lookupType :: Schema -> Name -> Maybe TypeDefinition
lookupType (Schema schema) name = Map.lookup name schema
Expand Down
8 changes: 5 additions & 3 deletions tests/ValidationTests.hs
@@ -1,4 +1,5 @@
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE DataKinds #-}

-- | Tests for query validation.
module ValidationTests (tests) where
Expand All @@ -11,8 +12,9 @@ import Test.Tasty (TestTree)
import Test.Tasty.Hspec (testSpec, describe, it, shouldBe)

import GraphQL.Internal.Name (Name)
import qualified Data.Map as Map
import qualified GraphQL.Internal.Syntax.AST as AST
import GraphQL.Internal.Schema (Schema)
import GraphQL.Internal.Schema (Schema, emptySchema)
import GraphQL.Internal.Validation
( ValidationError(..)
, findDuplicates
Expand All @@ -27,11 +29,11 @@ someName = "name"

dog :: Name
dog = "dog"

-- | Schema used for these tests. Since none of them do type-level stuff, we
-- don't need to define it.
schema :: Schema
schema = panic "schema evaluated. We weren't expecting that."
schema = emptySchema

tests :: IO TestTree
tests = testSpec "Validation" $ do
Expand Down

0 comments on commit 1c1393d

Please sign in to comment.