Make all exports explicit
This commit is contained in:
		@@ -1,5 +1,8 @@
 | 
				
			|||||||
-- | This module provides the functions to parse and execute @GraphQL@ queries.
 | 
					-- | This module provides the functions to parse and execute @GraphQL@ queries.
 | 
				
			||||||
module Language.GraphQL where
 | 
					module Language.GraphQL
 | 
				
			||||||
 | 
					    ( graphql
 | 
				
			||||||
 | 
					    , graphqlSubs
 | 
				
			||||||
 | 
					    ) where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import Control.Monad.IO.Class (MonadIO)
 | 
					import Control.Monad.IO.Class (MonadIO)
 | 
				
			||||||
import qualified Data.Text as T
 | 
					import qualified Data.Text as T
 | 
				
			||||||
 
 | 
				
			|||||||
@@ -2,8 +2,37 @@
 | 
				
			|||||||
--   <https://facebook.github.io/graphql/ Facebook's GraphQL Specification>.
 | 
					--   <https://facebook.github.io/graphql/ Facebook's GraphQL Specification>.
 | 
				
			||||||
--
 | 
					--
 | 
				
			||||||
-- Target AST for Parser.
 | 
					-- Target AST for Parser.
 | 
				
			||||||
 | 
					module Language.GraphQL.AST
 | 
				
			||||||
module Language.GraphQL.AST where
 | 
					    ( Alias
 | 
				
			||||||
 | 
					    , Argument(..)
 | 
				
			||||||
 | 
					    , Arguments
 | 
				
			||||||
 | 
					    , DefaultValue
 | 
				
			||||||
 | 
					    , Definition(..)
 | 
				
			||||||
 | 
					    , Directive(..)
 | 
				
			||||||
 | 
					    , Directives
 | 
				
			||||||
 | 
					    , Document
 | 
				
			||||||
 | 
					    , Field(..)
 | 
				
			||||||
 | 
					    , FragmentDefinition(..)
 | 
				
			||||||
 | 
					    , FragmentName
 | 
				
			||||||
 | 
					    , FragmentSpread(..)
 | 
				
			||||||
 | 
					    , InlineFragment(..)
 | 
				
			||||||
 | 
					    , ListValue
 | 
				
			||||||
 | 
					    , Name
 | 
				
			||||||
 | 
					    , NonNullType(..)
 | 
				
			||||||
 | 
					    , ObjectField(..)
 | 
				
			||||||
 | 
					    , ObjectValue
 | 
				
			||||||
 | 
					    , OperationDefinition(..)
 | 
				
			||||||
 | 
					    , OperationType(..)
 | 
				
			||||||
 | 
					    , Selection(..)
 | 
				
			||||||
 | 
					    , SelectionSet
 | 
				
			||||||
 | 
					    , SelectionSetOpt
 | 
				
			||||||
 | 
					    , Type(..)
 | 
				
			||||||
 | 
					    , TypeCondition
 | 
				
			||||||
 | 
					    , Value(..)
 | 
				
			||||||
 | 
					    , Variable
 | 
				
			||||||
 | 
					    , VariableDefinition(..)
 | 
				
			||||||
 | 
					    , VariableDefinitions
 | 
				
			||||||
 | 
					    ) where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import Data.Int (Int32)
 | 
					import Data.Int (Int32)
 | 
				
			||||||
import Data.List.NonEmpty (NonEmpty)
 | 
					import Data.List.NonEmpty (NonEmpty)
 | 
				
			||||||
 
 | 
				
			|||||||
@@ -1,5 +1,13 @@
 | 
				
			|||||||
-- | This is the AST meant to be executed.
 | 
					-- | This is the AST meant to be executed.
 | 
				
			||||||
module Language.GraphQL.AST.Core where
 | 
					module Language.GraphQL.AST.Core
 | 
				
			||||||
 | 
					    ( Argument(..)
 | 
				
			||||||
 | 
					    , Document
 | 
				
			||||||
 | 
					    , Field(..)
 | 
				
			||||||
 | 
					    , Name
 | 
				
			||||||
 | 
					    , ObjectField(..)
 | 
				
			||||||
 | 
					    , Operation(..)
 | 
				
			||||||
 | 
					    , Value(..)
 | 
				
			||||||
 | 
					    ) where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import Data.Int (Int32)
 | 
					import Data.Int (Int32)
 | 
				
			||||||
import Data.List.NonEmpty (NonEmpty)
 | 
					import Data.List.NonEmpty (NonEmpty)
 | 
				
			||||||
 
 | 
				
			|||||||
@@ -1,5 +1,7 @@
 | 
				
			|||||||
{-# LANGUAGE OverloadedStrings #-}
 | 
					{-# LANGUAGE OverloadedStrings #-}
 | 
				
			||||||
module Language.GraphQL.AST.Transform where
 | 
					module Language.GraphQL.AST.Transform
 | 
				
			||||||
 | 
					    ( document
 | 
				
			||||||
 | 
					    ) where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import Control.Applicative (empty)
 | 
					import Control.Applicative (empty)
 | 
				
			||||||
import Control.Monad ((<=<))
 | 
					import Control.Monad ((<=<))
 | 
				
			||||||
 
 | 
				
			|||||||
@@ -1,6 +1,9 @@
 | 
				
			|||||||
{-# LANGUAGE OverloadedStrings #-}
 | 
					{-# LANGUAGE OverloadedStrings #-}
 | 
				
			||||||
-- | This module defines a printer for the @GraphQL@ language.
 | 
					-- | This module defines a printer for the @GraphQL@ language.
 | 
				
			||||||
module Language.GraphQL.Encoder where
 | 
					module Language.GraphQL.Encoder
 | 
				
			||||||
 | 
					    ( document
 | 
				
			||||||
 | 
					    , spaced
 | 
				
			||||||
 | 
					    ) where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import Data.Foldable (fold)
 | 
					import Data.Foldable (fold)
 | 
				
			||||||
import Data.Monoid ((<>))
 | 
					import Data.Monoid ((<>))
 | 
				
			||||||
 
 | 
				
			|||||||
@@ -1,12 +1,12 @@
 | 
				
			|||||||
{-# LANGUAGE OverloadedStrings #-}
 | 
					{-# LANGUAGE OverloadedStrings #-}
 | 
				
			||||||
module Language.GraphQL.Error
 | 
					module Language.GraphQL.Error
 | 
				
			||||||
  ( parseError
 | 
					    ( parseError
 | 
				
			||||||
  , CollectErrsT
 | 
					    , CollectErrsT
 | 
				
			||||||
  , addErr
 | 
					    , addErr
 | 
				
			||||||
  , addErrMsg
 | 
					    , addErrMsg
 | 
				
			||||||
  , runCollectErrs
 | 
					    , runCollectErrs
 | 
				
			||||||
  , runAppendErrs
 | 
					    , runAppendErrs
 | 
				
			||||||
  ) where
 | 
					    ) where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import qualified Data.Aeson as Aeson
 | 
					import qualified Data.Aeson as Aeson
 | 
				
			||||||
import Data.Text (Text, pack)
 | 
					import Data.Text (Text, pack)
 | 
				
			||||||
 
 | 
				
			|||||||
@@ -2,7 +2,9 @@
 | 
				
			|||||||
 | 
					
 | 
				
			||||||
-- | This module provides the function to execute a @GraphQL@ request --
 | 
					-- | This module provides the function to execute a @GraphQL@ request --
 | 
				
			||||||
--   according to a 'Schema'.
 | 
					--   according to a 'Schema'.
 | 
				
			||||||
module Language.GraphQL.Execute (execute) where
 | 
					module Language.GraphQL.Execute
 | 
				
			||||||
 | 
					    ( execute
 | 
				
			||||||
 | 
					    ) where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import Control.Monad.IO.Class (MonadIO)
 | 
					import Control.Monad.IO.Class (MonadIO)
 | 
				
			||||||
import qualified Data.List.NonEmpty as NE
 | 
					import qualified Data.List.NonEmpty as NE
 | 
				
			||||||
 
 | 
				
			|||||||
@@ -1,6 +1,8 @@
 | 
				
			|||||||
{-# LANGUAGE LambdaCase #-}
 | 
					{-# LANGUAGE LambdaCase #-}
 | 
				
			||||||
{-# LANGUAGE OverloadedStrings #-}
 | 
					{-# LANGUAGE OverloadedStrings #-}
 | 
				
			||||||
module Language.GraphQL.Parser where
 | 
					module Language.GraphQL.Parser
 | 
				
			||||||
 | 
					    ( document
 | 
				
			||||||
 | 
					    ) where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import Control.Applicative ( Alternative(..)
 | 
					import Control.Applicative ( Alternative(..)
 | 
				
			||||||
                           , optional
 | 
					                           , optional
 | 
				
			||||||
 
 | 
				
			|||||||
@@ -3,27 +3,27 @@
 | 
				
			|||||||
-- | This module provides a representation of a @GraphQL@ Schema in addition to
 | 
					-- | This module provides a representation of a @GraphQL@ Schema in addition to
 | 
				
			||||||
--   functions for defining and manipulating Schemas.
 | 
					--   functions for defining and manipulating Schemas.
 | 
				
			||||||
module Language.GraphQL.Schema
 | 
					module Language.GraphQL.Schema
 | 
				
			||||||
  ( Resolver
 | 
					    ( Resolver
 | 
				
			||||||
  , Schema
 | 
					    , Schema
 | 
				
			||||||
  , Subs
 | 
					    , Subs
 | 
				
			||||||
  , object
 | 
					    , object
 | 
				
			||||||
  , objectA
 | 
					    , objectA
 | 
				
			||||||
  , scalar
 | 
					    , scalar
 | 
				
			||||||
  , scalarA
 | 
					    , scalarA
 | 
				
			||||||
  , enum
 | 
					    , enum
 | 
				
			||||||
  , enumA
 | 
					    , enumA
 | 
				
			||||||
  , resolve
 | 
					    , resolve
 | 
				
			||||||
  , wrappedEnum
 | 
					    , wrappedEnum
 | 
				
			||||||
  , wrappedEnumA
 | 
					    , wrappedEnumA
 | 
				
			||||||
  , wrappedObject
 | 
					    , wrappedObject
 | 
				
			||||||
  , wrappedObjectA
 | 
					    , wrappedObjectA
 | 
				
			||||||
  , wrappedScalar
 | 
					    , wrappedScalar
 | 
				
			||||||
  , wrappedScalarA
 | 
					    , wrappedScalarA
 | 
				
			||||||
  -- * AST Reexports
 | 
					    -- * AST Reexports
 | 
				
			||||||
  , Field
 | 
					    , Field
 | 
				
			||||||
  , Argument(..)
 | 
					    , Argument(..)
 | 
				
			||||||
  , Value(..)
 | 
					    , Value(..)
 | 
				
			||||||
  ) where
 | 
					    ) where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import Control.Monad.IO.Class (MonadIO(..))
 | 
					import Control.Monad.IO.Class (MonadIO(..))
 | 
				
			||||||
import Control.Monad.Trans.Class (lift)
 | 
					import Control.Monad.Trans.Class (lift)
 | 
				
			||||||
 
 | 
				
			|||||||
@@ -1,4 +1,6 @@
 | 
				
			|||||||
module Language.GraphQL.Trans where
 | 
					module Language.GraphQL.Trans
 | 
				
			||||||
 | 
					    ( ActionT(..)
 | 
				
			||||||
 | 
					    ) where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import Control.Applicative (Alternative(..))
 | 
					import Control.Applicative (Alternative(..))
 | 
				
			||||||
import Control.Monad (MonadPlus(..))
 | 
					import Control.Monad (MonadPlus(..))
 | 
				
			||||||
 
 | 
				
			|||||||
@@ -1,4 +1,4 @@
 | 
				
			|||||||
resolver: lts-13.27
 | 
					resolver: lts-13.28
 | 
				
			||||||
packages:
 | 
					packages:
 | 
				
			||||||
- '.'
 | 
					- '.'
 | 
				
			||||||
extra-deps: []
 | 
					extra-deps: []
 | 
				
			||||||
 
 | 
				
			|||||||
@@ -7,6 +7,6 @@ packages: []
 | 
				
			|||||||
snapshots:
 | 
					snapshots:
 | 
				
			||||||
- completed:
 | 
					- completed:
 | 
				
			||||||
    size: 500539
 | 
					    size: 500539
 | 
				
			||||||
    url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/13/27.yaml
 | 
					    url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/13/28.yaml
 | 
				
			||||||
    sha256: 690db832392afe55733b4c7023fd29b1b1c660ee42f1fb505b86b07394ca994e
 | 
					    sha256: cdde1bfb38fdee21c6acb73d506e78f7e12e0a73892adbbbe56374ebef4d3adf
 | 
				
			||||||
  original: lts-13.27
 | 
					  original: lts-13.28
 | 
				
			||||||
 
 | 
				
			|||||||
@@ -1,5 +1,21 @@
 | 
				
			|||||||
{-# LANGUAGE OverloadedStrings #-}
 | 
					{-# LANGUAGE OverloadedStrings #-}
 | 
				
			||||||
module Test.StarWars.Data where
 | 
					module Test.StarWars.Data
 | 
				
			||||||
 | 
					    ( Character
 | 
				
			||||||
 | 
					    , appearsIn
 | 
				
			||||||
 | 
					    , artoo
 | 
				
			||||||
 | 
					    , getDroid
 | 
				
			||||||
 | 
					    , getDroid'
 | 
				
			||||||
 | 
					    , getEpisode
 | 
				
			||||||
 | 
					    , getFriends
 | 
				
			||||||
 | 
					    , getHero
 | 
				
			||||||
 | 
					    , getHeroIO
 | 
				
			||||||
 | 
					    , getHuman
 | 
				
			||||||
 | 
					    , id_
 | 
				
			||||||
 | 
					    , homePlanet
 | 
				
			||||||
 | 
					    , name
 | 
				
			||||||
 | 
					    , secretBackstory
 | 
				
			||||||
 | 
					    , typeName
 | 
				
			||||||
 | 
					    ) where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import Data.Monoid (mempty)
 | 
					import Data.Monoid (mempty)
 | 
				
			||||||
import Control.Applicative ( Alternative(..)
 | 
					import Control.Applicative ( Alternative(..)
 | 
				
			||||||
 
 | 
				
			|||||||
@@ -1,6 +1,12 @@
 | 
				
			|||||||
{-# LANGUAGE LambdaCase #-}
 | 
					{-# LANGUAGE LambdaCase #-}
 | 
				
			||||||
{-# LANGUAGE OverloadedStrings #-}
 | 
					{-# LANGUAGE OverloadedStrings #-}
 | 
				
			||||||
module Test.StarWars.Schema where
 | 
					module Test.StarWars.Schema
 | 
				
			||||||
 | 
					    ( character
 | 
				
			||||||
 | 
					    , droid
 | 
				
			||||||
 | 
					    , hero
 | 
				
			||||||
 | 
					    , human
 | 
				
			||||||
 | 
					    , schema
 | 
				
			||||||
 | 
					    ) where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import Control.Monad.Trans.Except (throwE)
 | 
					import Control.Monad.Trans.Except (throwE)
 | 
				
			||||||
import Control.Monad.Trans.Class (lift)
 | 
					import Control.Monad.Trans.Class (lift)
 | 
				
			||||||
 
 | 
				
			|||||||
		Reference in New Issue
	
	Block a user