module Language.GraphQL.Validate.Validation
( Error(..)
, Rule(..)
, RuleT
, Validation(..)
) where
import Control.Monad.Trans.Reader (ReaderT)
import Data.Sequence (Seq)
import Language.GraphQL.AST.DirectiveLocation (DirectiveLocation(..))
import Language.GraphQL.AST.Document
import qualified Language.GraphQL.Type.In as In
import qualified Language.GraphQL.Type.Out as Out
import Language.GraphQL.Type.Schema (Schema)
data Error = Error
{ Error -> String
message :: String
, Error -> [Location]
locations :: [Location]
} deriving (Error -> Error -> Bool
(Error -> Error -> Bool) -> (Error -> Error -> Bool) -> Eq Error
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Error -> Error -> Bool
$c/= :: Error -> Error -> Bool
== :: Error -> Error -> Bool
$c== :: Error -> Error -> Bool
Eq, Int -> Error -> ShowS
[Error] -> ShowS
Error -> String
(Int -> Error -> ShowS)
-> (Error -> String) -> ([Error] -> ShowS) -> Show Error
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Error] -> ShowS
$cshowList :: [Error] -> ShowS
show :: Error -> String
$cshow :: Error -> String
showsPrec :: Int -> Error -> ShowS
$cshowsPrec :: Int -> Error -> ShowS
Show)
data Validation m = Validation
{ Validation m -> Document
ast :: Document
, Validation m -> Schema m
schema :: Schema m
}
data Rule m
= DefinitionRule (Definition -> RuleT m)
| OperationDefinitionRule (OperationDefinition -> RuleT m)
| FragmentDefinitionRule (FragmentDefinition -> RuleT m)
| SelectionRule (Maybe (Out.Type m) -> Selection -> RuleT m)
| FragmentRule (FragmentDefinition -> RuleT m) (InlineFragment -> RuleT m)
| FragmentSpreadRule (FragmentSpread -> RuleT m)
| FieldRule (Maybe (Out.Type m) -> Field -> RuleT m)
| ArgumentsRule (Maybe (Out.Type m) -> Field -> RuleT m) (Directive -> RuleT m)
| DirectivesRule (DirectiveLocation -> [Directive] -> RuleT m)
| VariablesRule ([VariableDefinition] -> RuleT m)
| ValueRule (Maybe In.Type -> Node Value -> RuleT m) (Maybe In.Type -> Node ConstValue -> RuleT m)
type RuleT m = ReaderT (Validation m) Seq Error