Drop support for GHC-7.8.4
This commit is contained in:
@ -19,7 +19,7 @@ import Data.GraphQL.Error
|
||||
-- executed according to the given 'Schema'.
|
||||
--
|
||||
-- Returns the response as an @Aeson.@'Aeson.Value'.
|
||||
graphql :: (Alternative m, Monad m) => Schema m -> Text -> m Aeson.Value
|
||||
graphql :: Alternative m => Schema m -> Text -> m Aeson.Value
|
||||
graphql = flip graphqlSubs $ const Nothing
|
||||
|
||||
-- | Takes a 'Schema', a variable substitution function and text
|
||||
@ -28,7 +28,7 @@ graphql = flip graphqlSubs $ const Nothing
|
||||
-- query and the query is then executed according to the given 'Schema'.
|
||||
--
|
||||
-- Returns the response as an @Aeson.@'Aeson.Value'.
|
||||
graphqlSubs :: (Alternative m, Monad m) => Schema m -> Subs -> Text -> m Aeson.Value
|
||||
graphqlSubs :: Alternative m => Schema m -> Subs -> Text -> m Aeson.Value
|
||||
graphqlSubs schema f =
|
||||
either parseError (execute schema f)
|
||||
. Attoparsec.parseOnly document
|
||||
|
@ -158,7 +158,7 @@ data InterfaceTypeDefinition = InterfaceTypeDefinition Name [FieldDefinition]
|
||||
data UnionTypeDefinition = UnionTypeDefinition Name [NamedType]
|
||||
deriving (Eq,Show)
|
||||
|
||||
data ScalarTypeDefinition = ScalarTypeDefinition Name
|
||||
newtype ScalarTypeDefinition = ScalarTypeDefinition Name
|
||||
deriving (Eq,Show)
|
||||
|
||||
data EnumTypeDefinition = EnumTypeDefinition Name [EnumValueDefinition]
|
||||
|
@ -1,12 +1,7 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
-- | This module defines a printer for the @GraphQL@ language.
|
||||
module Data.GraphQL.Encoder where
|
||||
|
||||
#if !MIN_VERSION_base(4,8,0)
|
||||
import Control.Applicative ((<$>))
|
||||
import Data.Monoid (Monoid, mconcat, mempty)
|
||||
#endif
|
||||
import Data.Monoid ((<>))
|
||||
|
||||
import Data.Text (Text, cons, intercalate, pack, snoc)
|
||||
|
@ -1,4 +1,3 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Data.GraphQL.Error (
|
||||
parseError,
|
||||
@ -15,12 +14,6 @@ import Data.Text (Text, pack)
|
||||
|
||||
import Control.Arrow ((&&&))
|
||||
|
||||
#if !MIN_VERSION_base(4,8,0)
|
||||
import Control.Applicative (Applicative, pure)
|
||||
import Data.Foldable (Foldable, concatMap)
|
||||
import Prelude hiding (concatMap)
|
||||
#endif
|
||||
|
||||
-- | Wraps a parse error into a list of errors.
|
||||
parseError :: Applicative f => String -> f Aeson.Value
|
||||
parseError s =
|
||||
|
@ -1,11 +1,7 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
-- | This module provides the function to execute a @GraphQL@ request --
|
||||
-- according to a 'Schema'.
|
||||
module Data.GraphQL.Execute (execute) where
|
||||
|
||||
#if !MIN_VERSION_base(4,8,0)
|
||||
import Control.Applicative ((<$>))
|
||||
#endif
|
||||
import Control.Applicative (Alternative)
|
||||
import Data.Maybe (catMaybes)
|
||||
|
||||
|
@ -1,14 +1,9 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
-- | This module defines a parser for @GraphQL@ request documents.
|
||||
module Data.GraphQL.Parser where
|
||||
|
||||
import Prelude hiding (takeWhile)
|
||||
|
||||
#if !MIN_VERSION_base(4,8,0)
|
||||
import Control.Applicative ((<$>), (<*>), (*>), (<*), (<$), pure)
|
||||
import Data.Monoid (Monoid, mempty)
|
||||
#endif
|
||||
import Control.Applicative ((<|>), empty, many, optional)
|
||||
import Control.Monad (when)
|
||||
import Data.Char (isDigit, isSpace)
|
||||
|
@ -1,4 +1,3 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
-- | This module provides a representation of a @GraphQL@ Schema in addition to
|
||||
@ -23,16 +22,8 @@ module Data.GraphQL.Schema
|
||||
, Value(..)
|
||||
) where
|
||||
|
||||
#if !MIN_VERSION_base(4,8,0)
|
||||
import Control.Applicative (pure)
|
||||
import Control.Arrow (first)
|
||||
import Data.Foldable (foldMap)
|
||||
import Data.Traversable (traverse)
|
||||
import Data.Monoid (Monoid(mempty,mappend))
|
||||
#else
|
||||
import Data.Bifunctor (first)
|
||||
import Data.Monoid (Alt(Alt,getAlt))
|
||||
#endif
|
||||
import Control.Applicative (Alternative((<|>), empty))
|
||||
import Data.Maybe (catMaybes)
|
||||
import Data.Foldable (fold)
|
||||
@ -142,11 +133,3 @@ field _ = Nothing
|
||||
-- | Returns a list of the 'Field's contained in the given 'SelectionSet'.
|
||||
fields :: SelectionSet -> [Field]
|
||||
fields = catMaybes . fmap field
|
||||
|
||||
#if !MIN_VERSION_base(4,8,0)
|
||||
newtype Alt f a = Alt {getAlt :: f a}
|
||||
|
||||
instance Alternative f => Monoid (Alt f a) where
|
||||
mempty = Alt empty
|
||||
Alt x `mappend` Alt y = Alt $ x <|> y
|
||||
#endif
|
||||
|
Reference in New Issue
Block a user