Added documentation of functions and modules and included tutorial.lhs.
This commit is contained in:
		@@ -1,3 +1,6 @@
 | 
				
			|||||||
 | 
					-- | The module Data.GraphQl provides the
 | 
				
			||||||
 | 
					--   functions graphql and graphqlSubs to parse
 | 
				
			||||||
 | 
					--   and execute GraphQL queries.
 | 
				
			||||||
module Data.GraphQL where
 | 
					module Data.GraphQL where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import Control.Applicative (Alternative)
 | 
					import Control.Applicative (Alternative)
 | 
				
			||||||
@@ -13,10 +16,19 @@ import Data.GraphQL.Schema
 | 
				
			|||||||
 | 
					
 | 
				
			||||||
import Data.GraphQL.Error
 | 
					import Data.GraphQL.Error
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | graphql takes a schema and text representing a GraphQL request document.
 | 
				
			||||||
 | 
					--   If the text parses correctly as a GraphQl query
 | 
				
			||||||
 | 
					--   the query is executed according to the given schema.
 | 
				
			||||||
 | 
					--   Returns the response to the query wrapped in an Aeson.Value.
 | 
				
			||||||
graphql :: (Alternative m, Monad m) => Schema m -> Text -> m Aeson.Value
 | 
					graphql :: (Alternative m, Monad m) => Schema m -> Text -> m Aeson.Value
 | 
				
			||||||
graphql = flip graphqlSubs $ const Nothing
 | 
					graphql = flip graphqlSubs $ const Nothing
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | graphqlsubs takes in a schema, a substitution and text representing
 | 
				
			||||||
 | 
					--   a GraphQL request document.
 | 
				
			||||||
 | 
					--   If the text parses correctly as a GraphQl query
 | 
				
			||||||
 | 
					--   the substitution is applied to the query and
 | 
				
			||||||
 | 
					--   the query is then executed according to the given schema.
 | 
				
			||||||
 | 
					--   Returns the response to the query wrapped in an Aeson.Value.
 | 
				
			||||||
graphqlSubs :: (Alternative m, Monad m) => Schema m -> Subs -> Text -> m Aeson.Value
 | 
					graphqlSubs :: (Alternative m, Monad m) => Schema m -> Subs -> Text -> m Aeson.Value
 | 
				
			||||||
graphqlSubs schema f =
 | 
					graphqlSubs schema f =
 | 
				
			||||||
    either parseError (execute schema f)
 | 
					    either parseError (execute schema f)
 | 
				
			||||||
 
 | 
				
			|||||||
@@ -1,3 +1,8 @@
 | 
				
			|||||||
 | 
					{- | This module defines an
 | 
				
			||||||
 | 
					     abstract syntax tree for the GraphQL language, based on
 | 
				
			||||||
 | 
					     <https://facebook.github.io/graphql/ Facebook's GraphQL Specification>.
 | 
				
			||||||
 | 
					-}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
module Data.GraphQL.AST where
 | 
					module Data.GraphQL.AST where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import Data.Int (Int32)
 | 
					import Data.Int (Int32)
 | 
				
			||||||
@@ -39,11 +44,33 @@ data Selection = SelectionField Field
 | 
				
			|||||||
               | SelectionInlineFragment InlineFragment
 | 
					               | SelectionInlineFragment InlineFragment
 | 
				
			||||||
                 deriving (Eq,Show)
 | 
					                 deriving (Eq,Show)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					{- | <https://facebook.github.io/graphql/#sec-Language.Query-Document.Fields Field Specification>
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					     A selection set is primarily composed of fields.
 | 
				
			||||||
 | 
					     A field describes one discrete piece of information
 | 
				
			||||||
 | 
					     available to request within a selection set.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					     Some fields describe complex data or relationships to other data.
 | 
				
			||||||
 | 
					     In order to further explore this data, a field may itself contain
 | 
				
			||||||
 | 
					     a selection set, allowing for deeply nested requests.
 | 
				
			||||||
 | 
					     All GraphQL operations must specify their selections down to
 | 
				
			||||||
 | 
					     fields which return scalar values to ensure an unambiguously
 | 
				
			||||||
 | 
					     shaped response.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-}
 | 
				
			||||||
data Field = Field Alias Name [Argument] [Directive] SelectionSet
 | 
					data Field = Field Alias Name [Argument] [Directive] SelectionSet
 | 
				
			||||||
             deriving (Eq,Show)
 | 
					             deriving (Eq,Show)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
type Alias = Name
 | 
					type Alias = Name
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					{- | <https://facebook.github.io/graphql/#sec-Language.Query-Document.Arguments Argument Specification>
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					     Fields are conceptually functions which return values,
 | 
				
			||||||
 | 
					     and occasionally accept arguments which alter their behavior.
 | 
				
			||||||
 | 
					     These arguments often map directly to function arguments within a
 | 
				
			||||||
 | 
					     GraphQL server’s implementation.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-}
 | 
				
			||||||
data Argument = Argument Name Value deriving (Eq,Show)
 | 
					data Argument = Argument Name Value deriving (Eq,Show)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- * Fragments
 | 
					-- * Fragments
 | 
				
			||||||
@@ -63,6 +90,18 @@ type TypeCondition = NamedType
 | 
				
			|||||||
 | 
					
 | 
				
			||||||
-- * Values
 | 
					-- * Values
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					{- | <https://facebook.github.io/graphql/#sec-Input-Values Input Value Specification>
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					    Field and directive arguments accept input values
 | 
				
			||||||
 | 
					    of various literal primitives; input values can be scalars,
 | 
				
			||||||
 | 
					    enumeration values, lists, or input objects.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					    If not defined as constant (for example, in DefaultValue),
 | 
				
			||||||
 | 
					    input values can be specified as a variable.
 | 
				
			||||||
 | 
					    List and inputs objects may also contain
 | 
				
			||||||
 | 
					    variables (unless defined to be constant).
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-}
 | 
				
			||||||
data Value = ValueVariable Variable
 | 
					data Value = ValueVariable Variable
 | 
				
			||||||
           | ValueInt Int32
 | 
					           | ValueInt Int32
 | 
				
			||||||
           -- GraphQL Float is double precison
 | 
					           -- GraphQL Float is double precison
 | 
				
			||||||
 
 | 
				
			|||||||
@@ -1,5 +1,7 @@
 | 
				
			|||||||
{-# LANGUAGE CPP #-}
 | 
					{-# LANGUAGE CPP #-}
 | 
				
			||||||
{-# LANGUAGE OverloadedStrings #-}
 | 
					{-# LANGUAGE OverloadedStrings #-}
 | 
				
			||||||
 | 
					-- | This module defines a printer
 | 
				
			||||||
 | 
					--   for the GraphQL language.
 | 
				
			||||||
module Data.GraphQL.Encoder where
 | 
					module Data.GraphQL.Encoder where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
#if !MIN_VERSION_base(4,8,0)
 | 
					#if !MIN_VERSION_base(4,8,0)
 | 
				
			||||||
 
 | 
				
			|||||||
@@ -1,5 +1,6 @@
 | 
				
			|||||||
{-# LANGUAGE CPP #-}
 | 
					{-# LANGUAGE CPP #-}
 | 
				
			||||||
{-# LANGUAGE OverloadedStrings #-}
 | 
					-- | This module provides the function execute which executes a GraphQL
 | 
				
			||||||
 | 
					--   request according to a given GraphQL schema.
 | 
				
			||||||
module Data.GraphQL.Execute (execute) where
 | 
					module Data.GraphQL.Execute (execute) where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
#if !MIN_VERSION_base(4,8,0)
 | 
					#if !MIN_VERSION_base(4,8,0)
 | 
				
			||||||
@@ -22,17 +23,25 @@ import Data.GraphQL.Error
 | 
				
			|||||||
     Returns the result of the query against the schema wrapped in a
 | 
					     Returns the result of the query against the schema wrapped in a
 | 
				
			||||||
     "data" field, or errors wrapped in a "errors field".
 | 
					     "data" field, or errors wrapped in a "errors field".
 | 
				
			||||||
-}
 | 
					-}
 | 
				
			||||||
execute :: Alternative m
 | 
					execute :: Alternative f
 | 
				
			||||||
  => Schema.Schema m -> Schema.Subs -> Document -> m Aeson.Value
 | 
					  => Schema.Schema f -> Schema.Subs -> Document -> f Aeson.Value
 | 
				
			||||||
execute (Schema resolvs) subs doc = runCollectErrs res
 | 
					execute (Schema resolvs) subs doc = runCollectErrs res
 | 
				
			||||||
  where res = Schema.resolvers resolvs $ rootFields subs doc
 | 
					  where res = Schema.resolvers resolvs $ rootFields subs doc
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | rootFields takes in a substitution and a GraphQL document.
 | 
				
			||||||
 | 
					--   If the document contains one query (and no other definitions)
 | 
				
			||||||
 | 
					--   it applies the substitution to the query's set of selections
 | 
				
			||||||
 | 
					--   and then returns their fields.
 | 
				
			||||||
rootFields :: Schema.Subs -> Document -> [Field]
 | 
					rootFields :: Schema.Subs -> Document -> [Field]
 | 
				
			||||||
rootFields subs (Document [DefinitionOperation (Query (Node _varDefs _ _ sels))]) =
 | 
					rootFields subs (Document [DefinitionOperation (Query (Node _varDefs _ _ sels))]) =
 | 
				
			||||||
    Schema.fields $ substitute subs <$> sels
 | 
					    Schema.fields $ substitute subs <$> sels
 | 
				
			||||||
rootFields _ _ = []
 | 
					rootFields _ _ = []
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | substitute takes in a substitution and a selection.
 | 
				
			||||||
 | 
					--   If the selection is a field it applies the substitution to the
 | 
				
			||||||
 | 
					--   field's arguments using subsArg,
 | 
				
			||||||
 | 
					--   and recursively applies the substitution to the arguments of fields
 | 
				
			||||||
 | 
					--   nested in the primary field.
 | 
				
			||||||
substitute :: Schema.Subs -> Selection -> Selection
 | 
					substitute :: Schema.Subs -> Selection -> Selection
 | 
				
			||||||
substitute subs (SelectionField (Field alias name args directives sels)) =
 | 
					substitute subs (SelectionField (Field alias name args directives sels)) =
 | 
				
			||||||
    SelectionField $ Field
 | 
					    SelectionField $ Field
 | 
				
			||||||
@@ -45,6 +54,9 @@ substitute subs (SelectionField (Field alias name args directives sels)) =
 | 
				
			|||||||
substitute _ sel = sel
 | 
					substitute _ sel = sel
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- TODO: Support different value types
 | 
					-- TODO: Support different value types
 | 
				
			||||||
 | 
					-- | subsArg takes in a substitution and an argument.
 | 
				
			||||||
 | 
					--   If the argument's value is a variable the substitution
 | 
				
			||||||
 | 
					--   is applied to the variable's name.
 | 
				
			||||||
subsArg :: Schema.Subs -> Argument -> Maybe Argument
 | 
					subsArg :: Schema.Subs -> Argument -> Maybe Argument
 | 
				
			||||||
subsArg subs (Argument n (ValueVariable (Variable v))) =
 | 
					subsArg subs (Argument n (ValueVariable (Variable v))) =
 | 
				
			||||||
    Argument n . ValueString <$> subs v
 | 
					    Argument n . ValueString <$> subs v
 | 
				
			||||||
 
 | 
				
			|||||||
@@ -1,5 +1,7 @@
 | 
				
			|||||||
{-# LANGUAGE CPP #-}
 | 
					{-# LANGUAGE CPP #-}
 | 
				
			||||||
{-# LANGUAGE OverloadedStrings #-}
 | 
					{-# LANGUAGE OverloadedStrings #-}
 | 
				
			||||||
 | 
					-- | This module defines a parser
 | 
				
			||||||
 | 
					--   for GraphQl request documents.
 | 
				
			||||||
module Data.GraphQL.Parser where
 | 
					module Data.GraphQL.Parser where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import Prelude hiding (takeWhile)
 | 
					import Prelude hiding (takeWhile)
 | 
				
			||||||
 
 | 
				
			|||||||
@@ -1,6 +1,9 @@
 | 
				
			|||||||
{-# LANGUAGE CPP #-}
 | 
					{-# LANGUAGE CPP #-}
 | 
				
			||||||
{-# LANGUAGE OverloadedStrings #-}
 | 
					{-# LANGUAGE OverloadedStrings #-}
 | 
				
			||||||
{-# LANGUAGE LambdaCase #-}
 | 
					{-# LANGUAGE LambdaCase #-}
 | 
				
			||||||
 | 
					-- | This module provides the type Schema,
 | 
				
			||||||
 | 
					--   representing a GraphQL schema, and functions for defining
 | 
				
			||||||
 | 
					--   a schema.
 | 
				
			||||||
module Data.GraphQL.Schema
 | 
					module Data.GraphQL.Schema
 | 
				
			||||||
  ( Schema(..)
 | 
					  ( Schema(..)
 | 
				
			||||||
  , Resolver
 | 
					  , Resolver
 | 
				
			||||||
@@ -44,54 +47,70 @@ import Control.Arrow
 | 
				
			|||||||
import Data.GraphQL.AST
 | 
					import Data.GraphQL.AST
 | 
				
			||||||
import Data.GraphQL.Error
 | 
					import Data.GraphQL.Error
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Schema represents a GraphQL schema.
 | 
				
			||||||
 | 
					--   f usually has to be an instance of Alternative.
 | 
				
			||||||
data Schema f = Schema [Resolver f]
 | 
					data Schema f = Schema [Resolver f]
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Resolver resolves a field in to a wrapped Aeson.Object with error information
 | 
				
			||||||
 | 
					--   (or empty). The wrapped f usually has to be an instance of Alternative.
 | 
				
			||||||
type Resolver f = Field -> CollectErrsT f Aeson.Object
 | 
					type Resolver f = Field -> CollectErrsT f Aeson.Object
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Subs represents a substitution.
 | 
				
			||||||
type Subs = Text -> Maybe Text
 | 
					type Subs = Text -> Maybe Text
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Objects represent a list of named fields, each of which
 | 
				
			||||||
 | 
					--   yield a value of a specific type.
 | 
				
			||||||
object :: Alternative f => Text -> [Resolver f] -> Resolver f
 | 
					object :: Alternative f => Text -> [Resolver f] -> Resolver f
 | 
				
			||||||
object name resolvs = objectA name $ \case
 | 
					object name resolvs = objectA name $ \case
 | 
				
			||||||
     [] -> resolvs
 | 
					     [] -> resolvs
 | 
				
			||||||
     _  -> empty
 | 
					     _  -> empty
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Fields can accept arguments to further specify the return value.
 | 
				
			||||||
objectA
 | 
					objectA
 | 
				
			||||||
  :: Alternative f
 | 
					  :: Alternative f
 | 
				
			||||||
  => Text -> ([Argument] -> [Resolver f]) -> Resolver f
 | 
					  => Text -> ([Argument] -> [Resolver f]) -> Resolver f
 | 
				
			||||||
objectA name f fld@(Field _ _ args _ sels) =
 | 
					objectA name f fld@(Field _ _ args _ sels) =
 | 
				
			||||||
    withField name (resolvers (f args) $ fields sels) fld
 | 
					    withField name (resolvers (f args) $ fields sels) fld
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | A scalar represents a primitive value, like a string or an integer.
 | 
				
			||||||
scalar :: (Alternative f, Aeson.ToJSON a) => Text -> a -> Resolver f
 | 
					scalar :: (Alternative f, Aeson.ToJSON a) => Text -> a -> Resolver f
 | 
				
			||||||
scalar name s = scalarA name $ \case
 | 
					scalar name s = scalarA name $ \case
 | 
				
			||||||
    [] -> pure s
 | 
					    [] -> pure s
 | 
				
			||||||
    _  -> empty
 | 
					    _  -> empty
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Arguments can be used to further specify a scalar's return value.
 | 
				
			||||||
scalarA
 | 
					scalarA
 | 
				
			||||||
  :: (Alternative f, Aeson.ToJSON a)
 | 
					  :: (Alternative f, Aeson.ToJSON a)
 | 
				
			||||||
  => Text -> ([Argument] -> f a) -> Resolver f
 | 
					  => Text -> ([Argument] -> f a) -> Resolver f
 | 
				
			||||||
scalarA name f fld@(Field _ _ args _ []) = withField name (errWrap $ f args) fld
 | 
					scalarA name f fld@(Field _ _ args _ []) = withField name (errWrap $ f args) fld
 | 
				
			||||||
scalarA _ _ _ = empty
 | 
					scalarA _ _ _ = empty
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Arrays are like objects but have an array of resolvers instead of a list.
 | 
				
			||||||
array :: Alternative f => Text -> [[Resolver f]] -> Resolver f
 | 
					array :: Alternative f => Text -> [[Resolver f]] -> Resolver f
 | 
				
			||||||
array name resolvs = arrayA name $ \case
 | 
					array name resolvs = arrayA name $ \case
 | 
				
			||||||
    [] -> resolvs
 | 
					    [] -> resolvs
 | 
				
			||||||
    _  -> empty
 | 
					    _  -> empty
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Arguments can be used to further specify an array's return values.
 | 
				
			||||||
arrayA
 | 
					arrayA
 | 
				
			||||||
  :: Alternative f
 | 
					  :: Alternative f
 | 
				
			||||||
  => Text -> ([Argument] -> [[Resolver f]]) -> Resolver f
 | 
					  => Text -> ([Argument] -> [[Resolver f]]) -> Resolver f
 | 
				
			||||||
arrayA name f fld@(Field _ _ args _ sels) =
 | 
					arrayA name f fld@(Field _ _ args _ sels) =
 | 
				
			||||||
     withField name (joinErrs $ traverse (flip resolvers $ fields sels) $ f args) fld
 | 
					     withField name (joinErrs $ traverse (flip resolvers $ fields sels) $ f args) fld
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | An enum represents one of a finite set of possible values.
 | 
				
			||||||
 | 
					--   Used in place of a scalar when the possible responses are easily enumerable.
 | 
				
			||||||
enum :: Alternative f => Text -> f [Text] -> Resolver f
 | 
					enum :: Alternative f => Text -> f [Text] -> Resolver f
 | 
				
			||||||
enum name enums = enumA name $ \case
 | 
					enum name enums = enumA name $ \case
 | 
				
			||||||
     [] -> enums
 | 
					     [] -> enums
 | 
				
			||||||
     _  -> empty
 | 
					     _  -> empty
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Arguments can be used to further specify an enum's return values.
 | 
				
			||||||
enumA :: Alternative f => Text -> ([Argument] -> f [Text]) -> Resolver f
 | 
					enumA :: Alternative f => Text -> ([Argument] -> f [Text]) -> Resolver f
 | 
				
			||||||
enumA name f fld@(Field _ _ args _ []) = withField name (errWrap $ f args) fld
 | 
					enumA name f fld@(Field _ _ args _ []) = withField name (errWrap $ f args) fld
 | 
				
			||||||
enumA _ _ _ = empty
 | 
					enumA _ _ _ = empty
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Used to implement a resolver with arguments.
 | 
				
			||||||
withField
 | 
					withField
 | 
				
			||||||
  :: (Alternative f, Aeson.ToJSON a)
 | 
					  :: (Alternative f, Aeson.ToJSON a)
 | 
				
			||||||
  => Text -> CollectErrsT f a -> Field -> CollectErrsT f (HashMap Text Aeson.Value)
 | 
					  => Text -> CollectErrsT f a -> Field -> CollectErrsT f (HashMap Text Aeson.Value)
 | 
				
			||||||
@@ -102,6 +121,9 @@ withField name f (Field alias name' _ _ _) =
 | 
				
			|||||||
     where
 | 
					     where
 | 
				
			||||||
       aliasOrName = if T.null alias then name' else alias
 | 
					       aliasOrName = if T.null alias then name' else alias
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | resolvers takes a list of resolvers and a list of fields,
 | 
				
			||||||
 | 
					--   and applies each resolver to each field. Resolves into a value
 | 
				
			||||||
 | 
					--   containing the resolved field, or a null value and error information.
 | 
				
			||||||
resolvers :: Alternative f => [Resolver f] -> [Field] -> CollectErrsT f Aeson.Value
 | 
					resolvers :: Alternative f => [Resolver f] -> [Field] -> CollectErrsT f Aeson.Value
 | 
				
			||||||
resolvers resolvs =
 | 
					resolvers resolvs =
 | 
				
			||||||
    fmap (first Aeson.toJSON . fold)
 | 
					    fmap (first Aeson.toJSON . fold)
 | 
				
			||||||
@@ -111,10 +133,13 @@ resolvers resolvs =
 | 
				
			|||||||
                  msg = T.unwords ["field", name, "not resolved."]
 | 
					                  msg = T.unwords ["field", name, "not resolved."]
 | 
				
			||||||
                  aliasOrName = if T.null alias then name else alias
 | 
					                  aliasOrName = if T.null alias then name else alias
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Checks whether the given selection contains a field and
 | 
				
			||||||
 | 
					--   returns the field if so, else returns Nothing.
 | 
				
			||||||
field :: Selection -> Maybe Field
 | 
					field :: Selection -> Maybe Field
 | 
				
			||||||
field (SelectionField x) = Just x
 | 
					field (SelectionField x) = Just x
 | 
				
			||||||
field _ = Nothing
 | 
					field _ = Nothing
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Returns a list of the fields contained in the given selection set.
 | 
				
			||||||
fields :: SelectionSet -> [Field]
 | 
					fields :: SelectionSet -> [Field]
 | 
				
			||||||
fields = catMaybes . fmap field
 | 
					fields = catMaybes . fmap field
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 
 | 
				
			|||||||
@@ -16,6 +16,7 @@ build-type:          Simple
 | 
				
			|||||||
cabal-version:       >=1.10
 | 
					cabal-version:       >=1.10
 | 
				
			||||||
tested-with:         GHC == 7.8.4, GHC == 7.10.3
 | 
					tested-with:         GHC == 7.8.4, GHC == 7.10.3
 | 
				
			||||||
extra-source-files:  README.md CHANGELOG.md stack.yaml
 | 
					extra-source-files:  README.md CHANGELOG.md stack.yaml
 | 
				
			||||||
 | 
					                     docs/tutorial/tutorial.lhs
 | 
				
			||||||
data-files:          tests/data/*.graphql
 | 
					data-files:          tests/data/*.graphql
 | 
				
			||||||
                     tests/data/*.min.graphql
 | 
					                     tests/data/*.min.graphql
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 
 | 
				
			|||||||
		Reference in New Issue
	
	Block a user