Validate required input fields
This commit is contained in:
@ -1,5 +1,7 @@
|
||||
{-# LANGUAGE DuplicateRecordFields #-}
|
||||
{-# LANGUAGE ExplicitForAll #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE RecordWildCards #-}
|
||||
{-# LANGUAGE Safe #-}
|
||||
|
||||
-- | This module defines an abstract syntax tree for the @GraphQL@ language. It
|
||||
@ -75,10 +77,13 @@ instance Ord Location where
|
||||
|
||||
-- | Contains some tree node with a location.
|
||||
data Node a = Node
|
||||
{ value :: a
|
||||
{ node :: a
|
||||
, location :: Location
|
||||
} deriving (Eq, Show)
|
||||
|
||||
instance Functor Node where
|
||||
fmap f Node{..} = Node (f node) location
|
||||
|
||||
-- ** Document
|
||||
|
||||
-- | GraphQL document.
|
||||
@ -241,8 +246,11 @@ data ConstValue
|
||||
-- | Key-value pair.
|
||||
--
|
||||
-- A list of 'ObjectField's represents a GraphQL object type.
|
||||
data ObjectField a = ObjectField Name a Location
|
||||
deriving (Eq, Show)
|
||||
data ObjectField a = ObjectField
|
||||
{ name :: Name
|
||||
, value :: Node a
|
||||
, location :: Location
|
||||
} deriving (Eq, Show)
|
||||
|
||||
-- ** Variables
|
||||
|
||||
|
@ -1,6 +1,7 @@
|
||||
{-# LANGUAGE ExplicitForAll #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
{-# LANGUAGE RecordWildCards #-}
|
||||
{-# LANGUAGE Safe #-}
|
||||
|
||||
-- | This module defines a minifier and a printer for the @GraphQL@ language.
|
||||
@ -101,7 +102,7 @@ variableDefinition formatter variableDefinition' =
|
||||
in variable variableName
|
||||
<> eitherFormat formatter ": " ":"
|
||||
<> type' variableType
|
||||
<> maybe mempty (defaultValue formatter) (Full.value <$> defaultValue')
|
||||
<> maybe mempty (defaultValue formatter) (Full.node <$> defaultValue')
|
||||
|
||||
defaultValue :: Formatter -> Full.ConstValue -> Lazy.Text
|
||||
defaultValue formatter val
|
||||
@ -164,7 +165,7 @@ argument :: Formatter -> Full.Argument -> Lazy.Text
|
||||
argument formatter (Full.Argument name value' _)
|
||||
= Lazy.Text.fromStrict name
|
||||
<> colon formatter
|
||||
<> value formatter (Full.value value')
|
||||
<> value formatter (Full.node value')
|
||||
|
||||
-- * Fragments
|
||||
|
||||
@ -222,8 +223,8 @@ fromConstValue (Full.ConstEnum x) = Full.Enum x
|
||||
fromConstValue (Full.ConstList x) = Full.List $ fromConstValue <$> x
|
||||
fromConstValue (Full.ConstObject x) = Full.Object $ fromConstObjectField <$> x
|
||||
where
|
||||
fromConstObjectField (Full.ObjectField key value' location) =
|
||||
Full.ObjectField key (fromConstValue value') location
|
||||
fromConstObjectField Full.ObjectField{value = value', ..} =
|
||||
Full.ObjectField name (fromConstValue <$> value') location
|
||||
|
||||
booleanValue :: Bool -> Lazy.Text
|
||||
booleanValue True = "true"
|
||||
@ -292,7 +293,7 @@ objectValue formatter = intercalate $ objectField formatter
|
||||
. fmap f
|
||||
|
||||
objectField :: Formatter -> Full.ObjectField Full.Value -> Lazy.Text
|
||||
objectField formatter (Full.ObjectField name value' _) =
|
||||
objectField formatter (Full.ObjectField name (Full.Node value' _) _) =
|
||||
Lazy.Text.fromStrict name <> colon formatter <> value formatter value'
|
||||
|
||||
-- | Converts a 'Type' a type into a string.
|
||||
|
@ -461,7 +461,7 @@ value = Full.Variable <$> variable
|
||||
<|> Full.String <$> stringValue
|
||||
<|> Full.Enum <$> try enumValue
|
||||
<|> Full.List <$> brackets (some value)
|
||||
<|> Full.Object <$> braces (some $ objectField value)
|
||||
<|> Full.Object <$> braces (some $ objectField $ valueNode value)
|
||||
<?> "Value"
|
||||
|
||||
constValue :: Parser Full.ConstValue
|
||||
@ -472,7 +472,7 @@ constValue = Full.ConstFloat <$> try float
|
||||
<|> Full.ConstString <$> stringValue
|
||||
<|> Full.ConstEnum <$> try enumValue
|
||||
<|> Full.ConstList <$> brackets (some constValue)
|
||||
<|> Full.ConstObject <$> braces (some $ objectField constValue)
|
||||
<|> Full.ConstObject <$> braces (some $ objectField $ valueNode constValue)
|
||||
<?> "Value"
|
||||
|
||||
booleanValue :: Parser Bool
|
||||
@ -493,7 +493,7 @@ stringValue = blockString <|> string <?> "StringValue"
|
||||
nullValue :: Parser Text
|
||||
nullValue = symbol "null" <?> "NullValue"
|
||||
|
||||
objectField :: Parser a -> Parser (Full.ObjectField a)
|
||||
objectField :: forall a. Parser (Full.Node a) -> Parser (Full.ObjectField a)
|
||||
objectField valueParser = label "ObjectField" $ do
|
||||
location <- getLocation
|
||||
fieldName <- name
|
||||
|
Reference in New Issue
Block a user