Skip to content

Commit 12ad8eb

Browse files
committed
Drop custom NonEmptyList
Compels us to change API methods to handle possible error case of field lists and union object lists being empty, which in turn forces a change to the API.
1 parent 54b0a67 commit 12ad8eb

File tree

6 files changed

+75
-51
lines changed

6 files changed

+75
-51
lines changed

src/GraphQL.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,7 @@ import Protolude
2727
import Data.Attoparsec.Text (parseOnly, endOfInput)
2828
import Data.List.NonEmpty (NonEmpty(..))
2929
import qualified Data.List.NonEmpty as NonEmpty
30-
import GraphQL.API (HasObjectDefinition(..))
30+
import GraphQL.API (HasObjectDefinition(..), SchemaError(..))
3131
import GraphQL.Internal.Execution
3232
( VariableValues
3333
, ExecutionError
@@ -52,7 +52,7 @@ import GraphQL.Internal.Output
5252
import GraphQL.Internal.Schema (Schema)
5353
import qualified GraphQL.Internal.Schema as Schema
5454
import GraphQL.Resolver (HasResolver(..), Result(..))
55-
import GraphQL.Value (Name, NameError, Value, pattern ValueObject)
55+
import GraphQL.Value (Name, Value, pattern ValueObject)
5656

5757
-- | Errors that can happen while processing a query document.
5858
data QueryError
@@ -66,7 +66,7 @@ data QueryError
6666
-- | Validated, but failed during execution.
6767
| ExecutionError ExecutionError
6868
-- | Error in the schema.
69-
| SchemaError NameError
69+
| SchemaError SchemaError
7070
-- | Got a value that wasn't an object.
7171
| NonObjectResult Value
7272
deriving (Eq, Show)

src/GraphQL/API.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@ module GraphQL.API
1414
, Defaultable(..)
1515
, HasObjectDefinition(..)
1616
, HasAnnotatedInputType(..)
17+
, SchemaError(..)
1718
) where
1819

1920
import GraphQL.Internal.API
@@ -29,4 +30,5 @@ import GraphQL.Internal.API
2930
, Defaultable(..)
3031
, HasObjectDefinition(..)
3132
, HasAnnotatedInputType(..)
33+
, SchemaError(..)
3234
)

src/GraphQL/Internal/API.hs

Lines changed: 57 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -27,6 +27,8 @@ module GraphQL.Internal.API
2727
, HasAnnotatedInputType
2828
, HasObjectDefinition(..)
2929
, getArgumentDefinition
30+
, SchemaError(..)
31+
, nameFromSymbol
3032
-- | Exported for testing.
3133
, getFieldDefinition
3234
, getInterfaceDefinition
@@ -35,13 +37,16 @@ module GraphQL.Internal.API
3537

3638
import Protolude hiding (Enum, TypeError)
3739

40+
import qualified Data.List.NonEmpty as NonEmpty
3841
import GHC.Generics ((:*:)(..))
3942
import GHC.TypeLits (Symbol, KnownSymbol, TypeError, ErrorMessage(..))
4043
import GHC.Types (Type)
4144

4245
import qualified GraphQL.Internal.Schema as Schema
43-
import GraphQL.Internal.Name (Name, NameError, nameFromSymbol)
46+
import qualified GraphQL.Internal.Name as Name
47+
import GraphQL.Internal.Name (Name, NameError)
4448
import GraphQL.Internal.API.Enum (GraphQLEnum(..))
49+
import GraphQL.Internal.Output (GraphQLError(..))
4550

4651
-- $setup
4752
-- >>> :set -XDataKinds -XTypeOperators
@@ -83,6 +88,21 @@ data Field (name :: Symbol) (fieldType :: Type)
8388
data Argument (name :: Symbol) (argType :: Type)
8489

8590

91+
-- | The type-level schema was somehow invalid.
92+
data SchemaError
93+
= NameError NameError
94+
| EmptyFieldList
95+
| EmptyUnion
96+
deriving (Eq, Show)
97+
98+
instance GraphQLError SchemaError where
99+
formatError (NameError err) = formatError err
100+
formatError EmptyFieldList = "Empty field list in type definition"
101+
formatError EmptyUnion = "Empty object list in union"
102+
103+
nameFromSymbol :: forall (n :: Symbol). KnownSymbol n => Either SchemaError Name
104+
nameFromSymbol = first NameError (Name.nameFromSymbol @n)
105+
86106
-- | Specify a default value for a type in a GraphQL schema.
87107
--
88108
-- GraphQL schema can have default values in certain places. For example,
@@ -115,41 +135,52 @@ instance Defaultable (Maybe a) where
115135
cons :: a -> [a] -> [a]
116136
cons = (:)
117137

138+
singleton :: a -> NonEmpty a
139+
singleton x = x :| []
140+
118141
-- Transform into a Schema definition
119142
class HasObjectDefinition a where
120143
-- Todo rename to getObjectTypeDefinition
121-
getDefinition :: Either NameError Schema.ObjectTypeDefinition
144+
getDefinition :: Either SchemaError Schema.ObjectTypeDefinition
122145

123146
class HasFieldDefinition a where
124-
getFieldDefinition :: Either NameError Schema.FieldDefinition
147+
getFieldDefinition :: Either SchemaError Schema.FieldDefinition
125148

126149

127150
-- Fields
128151
class HasFieldDefinitions a where
129-
getFieldDefinitions :: Either NameError [Schema.FieldDefinition]
152+
getFieldDefinitions :: Either SchemaError (NonEmpty Schema.FieldDefinition)
130153

131154
instance forall a as. (HasFieldDefinition a, HasFieldDefinitions as) => HasFieldDefinitions (a:as) where
132-
getFieldDefinitions = cons <$> getFieldDefinition @a <*> getFieldDefinitions @as
155+
getFieldDefinitions =
156+
case getFieldDefinitions @as of
157+
Left EmptyFieldList -> singleton <$> getFieldDefinition @a
158+
Left err -> Left err
159+
Right fields -> NonEmpty.cons <$> getFieldDefinition @a <*> pure fields
133160

134161
instance HasFieldDefinitions '[] where
135-
getFieldDefinitions = pure []
162+
getFieldDefinitions = Left EmptyFieldList
136163

137164

138165
-- object types from union type lists, e.g. for
139166
-- Union "Horse" '[Leg, Head, Tail]
140167
-- ^^^^^^^^^^^^^^^^^^ this part
141168
class HasUnionTypeObjectTypeDefinitions a where
142-
getUnionTypeObjectTypeDefinitions :: Either NameError [Schema.ObjectTypeDefinition]
169+
getUnionTypeObjectTypeDefinitions :: Either SchemaError (NonEmpty Schema.ObjectTypeDefinition)
143170

144171
instance forall a as. (HasObjectDefinition a, HasUnionTypeObjectTypeDefinitions as) => HasUnionTypeObjectTypeDefinitions (a:as) where
145-
getUnionTypeObjectTypeDefinitions = cons <$> getDefinition @a <*> getUnionTypeObjectTypeDefinitions @as
172+
getUnionTypeObjectTypeDefinitions =
173+
case getUnionTypeObjectTypeDefinitions @as of
174+
Left EmptyUnion -> singleton <$> getDefinition @a
175+
Left err -> Left err
176+
Right objects -> NonEmpty.cons <$> getDefinition @a <*> pure objects
146177

147178
instance HasUnionTypeObjectTypeDefinitions '[] where
148-
getUnionTypeObjectTypeDefinitions = pure []
179+
getUnionTypeObjectTypeDefinitions = Left EmptyUnion
149180

150181
-- Interfaces
151182
class HasInterfaceDefinitions a where
152-
getInterfaceDefinitions :: Either NameError Schema.Interfaces
183+
getInterfaceDefinitions :: Either SchemaError Schema.Interfaces
153184

154185
instance forall a as. (HasInterfaceDefinition a, HasInterfaceDefinitions as) => HasInterfaceDefinitions (a:as) where
155186
getInterfaceDefinitions = cons <$> getInterfaceDefinition @a <*> getInterfaceDefinitions @as
@@ -158,12 +189,12 @@ instance HasInterfaceDefinitions '[] where
158189
getInterfaceDefinitions = pure []
159190

160191
class HasInterfaceDefinition a where
161-
getInterfaceDefinition :: Either NameError Schema.InterfaceTypeDefinition
192+
getInterfaceDefinition :: Either SchemaError Schema.InterfaceTypeDefinition
162193

163194
instance forall ks fields. (KnownSymbol ks, HasFieldDefinitions fields) => HasInterfaceDefinition (Interface ks fields) where
164195
getInterfaceDefinition =
165196
let name = nameFromSymbol @ks
166-
fields = Schema.NonEmptyList <$> getFieldDefinitions @fields
197+
fields = getFieldDefinitions @fields
167198
in Schema.InterfaceTypeDefinition <$> name <*> fields
168199

169200
-- Give users some help if they don't terminate Arguments with a Field:
@@ -183,7 +214,7 @@ instance forall t ks. (KnownSymbol ks, HasAnnotatedType t) => HasFieldDefinition
183214
in Schema.FieldDefinition <$> name <*> pure [] <*> getAnnotatedType @t
184215

185216
class HasArgumentDefinition a where
186-
getArgumentDefinition :: Either NameError Schema.ArgumentDefinition
217+
getArgumentDefinition :: Either SchemaError Schema.ArgumentDefinition
187218

188219
instance forall ks t. (KnownSymbol ks, HasAnnotatedInputType t) => HasArgumentDefinition (Argument ks t) where
189220
getArgumentDefinition = Schema.ArgumentDefinition <$> argName <*> argType <*> defaultValue
@@ -205,7 +236,7 @@ instance forall ks is fields.
205236
getDefinition =
206237
let name = nameFromSymbol @ks
207238
interfaces = getInterfaceDefinitions @is
208-
fields = Schema.NonEmptyList <$> getFieldDefinitions @fields
239+
fields = getFieldDefinitions @fields
209240
in Schema.ObjectTypeDefinition <$> name <*> interfaces <*> fields
210241

211242
-- Builtin output types (annotated types)
@@ -215,7 +246,7 @@ class HasAnnotatedType a where
215246
-- forget this. Maybe we can flip the internal encoding to be
216247
-- non-null by default and needing explicit null-encoding (via
217248
-- Maybe).
218-
getAnnotatedType :: Either NameError (Schema.AnnotatedType Schema.GType)
249+
getAnnotatedType :: Either SchemaError (Schema.AnnotatedType Schema.GType)
219250

220251
-- | Turn a non-null type into the optional version of its own type.
221252
dropNonNull :: Schema.AnnotatedType t -> Schema.AnnotatedType t
@@ -228,7 +259,7 @@ instance forall a. HasAnnotatedType a => HasAnnotatedType (Maybe a) where
228259
-- see TODO in HasAnnotatedType class
229260
getAnnotatedType = dropNonNull <$> getAnnotatedType @a
230261

231-
builtinType :: Schema.Builtin -> Either NameError (Schema.AnnotatedType Schema.GType)
262+
builtinType :: Schema.Builtin -> Either SchemaError (Schema.AnnotatedType Schema.GType)
232263
builtinType = pure . Schema.TypeNonNull . Schema.NonNullTypeNamed . Schema.BuiltinType
233264

234265
-- TODO(jml): Given that AnnotatedType is parametrised, we can probably reduce
@@ -263,13 +294,13 @@ instance forall ks enum. (KnownSymbol ks, GraphQLEnum enum) => HasAnnotatedType
263294
getAnnotatedType = do
264295
let name = nameFromSymbol @ks
265296
let enums = sequenceA (enumValues @enum) :: Either NameError [Schema.Name]
266-
let et = Schema.EnumTypeDefinition <$> name <*> map (map Schema.EnumValueDefinition) enums
297+
let et = Schema.EnumTypeDefinition <$> name <*> map (map Schema.EnumValueDefinition) (first NameError enums)
267298
Schema.TypeNonNull . Schema.NonNullTypeNamed . Schema.DefinedType . Schema.TypeDefinitionEnum <$> et
268299

269300
instance forall ks as. (KnownSymbol ks, HasUnionTypeObjectTypeDefinitions as) => HasAnnotatedType (Union ks as) where
270301
getAnnotatedType =
271302
let name = nameFromSymbol @ks
272-
types = Schema.NonEmptyList <$> getUnionTypeObjectTypeDefinitions @as
303+
types = getUnionTypeObjectTypeDefinitions @as
273304
in (Schema.TypeNamed . Schema.DefinedType . Schema.TypeDefinitionUnion) <$> (Schema.UnionTypeDefinition <$> name <*> types)
274305

275306
-- Help users with better type errors
@@ -281,14 +312,14 @@ instance TypeError ('Text "Cannot encode Integer because it has arbitrary size b
281312
-- Builtin input types
282313
class HasAnnotatedInputType a where
283314
-- See TODO comment in "HasAnnotatedType" class for nullability.
284-
getAnnotatedInputType :: Either NameError (Schema.AnnotatedType Schema.InputType)
285-
default getAnnotatedInputType :: (Generic a, GenericAnnotatedInputType (Rep a)) => Either NameError (Schema.AnnotatedType Schema.InputType)
315+
getAnnotatedInputType :: Either SchemaError (Schema.AnnotatedType Schema.InputType)
316+
default getAnnotatedInputType :: (Generic a, GenericAnnotatedInputType (Rep a)) => Either SchemaError (Schema.AnnotatedType Schema.InputType)
286317
getAnnotatedInputType = genericGetAnnotatedInputType @(Rep a)
287318

288319
instance forall a. HasAnnotatedInputType a => HasAnnotatedInputType (Maybe a) where
289320
getAnnotatedInputType = dropNonNull <$> getAnnotatedInputType @a
290321

291-
builtinInputType :: Schema.Builtin -> Either NameError (Schema.AnnotatedType Schema.InputType)
322+
builtinInputType :: Schema.Builtin -> Either SchemaError (Schema.AnnotatedType Schema.InputType)
292323
builtinInputType = pure . Schema.TypeNonNull . Schema.NonNullTypeNamed . Schema.BuiltinInputType
293324

294325
instance HasAnnotatedInputType Int where
@@ -316,16 +347,16 @@ instance forall ks enum. (KnownSymbol ks, GraphQLEnum enum) => HasAnnotatedInput
316347
getAnnotatedInputType = do
317348
let name = nameFromSymbol @ks
318349
enums = sequenceA (enumValues @enum) :: Either NameError [Schema.Name]
319-
let et = Schema.EnumTypeDefinition <$> name <*> map (map Schema.EnumValueDefinition) enums
350+
let et = Schema.EnumTypeDefinition <$> name <*> map (map Schema.EnumValueDefinition) (first NameError enums)
320351
Schema.TypeNonNull . Schema.NonNullTypeNamed . Schema.DefinedInputType . Schema.InputTypeDefinitionEnum <$> et
321352

322353

323354
-- Generic getAnnotatedInputType function
324355
class GenericAnnotatedInputType (f :: Type -> Type) where
325-
genericGetAnnotatedInputType :: Either NameError (Schema.AnnotatedType Schema.InputType)
356+
genericGetAnnotatedInputType :: Either SchemaError (Schema.AnnotatedType Schema.InputType)
326357

327358
class GenericInputObjectFieldDefinitions (f :: Type -> Type) where
328-
genericGetInputObjectFieldDefinitions :: Either NameError [Schema.InputObjectFieldDefinition]
359+
genericGetInputObjectFieldDefinitions :: Either SchemaError (NonEmpty Schema.InputObjectFieldDefinition)
329360

330361
instance forall dataName consName records s l p.
331362
( KnownSymbol dataName
@@ -341,7 +372,6 @@ instance forall dataName consName records s l p.
341372
. Schema.DefinedInputType
342373
. Schema.InputTypeDefinitionObject
343374
. Schema.InputObjectTypeDefinition name
344-
. Schema.NonEmptyList
345375
) (genericGetInputObjectFieldDefinitions @records)
346376

347377
instance forall wrappedType fieldName rest u s l.
@@ -354,7 +384,7 @@ instance forall wrappedType fieldName rest u s l.
354384
annotatedInputType <- getAnnotatedInputType @wrappedType
355385
let l = Schema.InputObjectFieldDefinition name annotatedInputType Nothing
356386
r <- genericGetInputObjectFieldDefinitions @rest
357-
pure (l:r)
387+
pure (NonEmpty.cons l r)
358388

359389
instance forall wrappedType fieldName u s l.
360390
( KnownSymbol fieldName
@@ -364,4 +394,4 @@ instance forall wrappedType fieldName u s l.
364394
name <- nameFromSymbol @fieldName
365395
annotatedInputType <- getAnnotatedInputType @wrappedType
366396
let l = Schema.InputObjectFieldDefinition name annotatedInputType Nothing
367-
pure [l]
397+
pure (l :| [])

src/GraphQL/Internal/Resolver.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -53,7 +53,7 @@ import GraphQL.Value
5353
, FromValue(..)
5454
, ToValue(..)
5555
)
56-
import GraphQL.Internal.Name (Name, NameError(..), HasName(..), nameFromSymbol)
56+
import GraphQL.Internal.Name (Name, HasName(..))
5757
import qualified GraphQL.Internal.OrderedMap as OrderedMap
5858
import GraphQL.Internal.Output (GraphQLError(..))
5959
import GraphQL.Internal.Validation
@@ -68,7 +68,7 @@ import GraphQL.Internal.Validation
6868

6969
data ResolverError
7070
-- | There was a problem in the schema. Server-side problem.
71-
= SchemaError NameError
71+
= SchemaError API.SchemaError
7272
-- | Couldn't find the requested field in the object. A client-side problem.
7373
| FieldNotFoundError Name
7474
-- | No value provided for name, and no default specified. Client-side problem.
@@ -216,7 +216,7 @@ resolveField :: forall dispatchType (m :: Type -> Type).
216216
=> FieldHandler m dispatchType -> m ResolveFieldResult -> Field Value -> m ResolveFieldResult
217217
resolveField handler nextHandler field =
218218
-- check name before
219-
case nameFromSymbol @(FieldName dispatchType) of
219+
case API.nameFromSymbol @(FieldName dispatchType) of
220220
Left err -> pure (Result [SchemaError err] (Just GValue.ValueNull))
221221
Right name'
222222
| getName field == name' ->
@@ -281,7 +281,7 @@ instance forall ksK t f m name.
281281
, Monad m
282282
) => BuildFieldResolver m (EnumArgument (API.Argument ksK (API.Enum name t)) f) where
283283
buildFieldResolver handler field = do
284-
argName <- first SchemaError (nameFromSymbol @ksK)
284+
argName <- first SchemaError (API.nameFromSymbol @ksK)
285285
value <- case lookupArgument field argName of
286286
Nothing -> valueMissing @t argName
287287
Just (ValueEnum enum) -> first (InvalidValue argName) (API.enumFromValue @t enum)

src/GraphQL/Internal/Schema.hs

Lines changed: 5 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,3 @@
1-
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
21
{-# OPTIONS_HADDOCK not-home #-}
32

43
-- | Description: Fully realized GraphQL schema type system at the Haskell value level
@@ -21,7 +20,6 @@ module GraphQL.Internal.Schema
2120
, FieldDefinition(..)
2221
, Interfaces
2322
, InterfaceTypeDefinition(..)
24-
, NonEmptyList(..)
2523
, ObjectTypeDefinition(..)
2624
, UnionTypeDefinition(..)
2725
-- ** Input types
@@ -64,9 +62,6 @@ makeSchema = Schema . getDefinedTypes
6462
lookupType :: Schema -> Name -> Maybe TypeDefinition
6563
lookupType (Schema schema) name = Map.lookup name schema
6664

67-
-- XXX: Use the built-in NonEmptyList in Haskell
68-
newtype NonEmptyList a = NonEmptyList [a] deriving (Eq, Ord, Show, Functor, Foldable)
69-
7065
-- | A thing that defines types. Excludes definitions of input types.
7166
class DefinesTypes t where
7267
-- | Get the types defined by @t@
@@ -141,7 +136,7 @@ instance DefinesTypes TypeDefinition where
141136
TypeDefinitionTypeExtension _ ->
142137
panic "TODO: we should remove the 'extend' behaviour entirely"
143138

144-
data ObjectTypeDefinition = ObjectTypeDefinition Name Interfaces (NonEmptyList FieldDefinition)
139+
data ObjectTypeDefinition = ObjectTypeDefinition Name Interfaces (NonEmpty FieldDefinition)
145140
deriving (Eq, Ord, Show)
146141

147142
instance HasName ObjectTypeDefinition where
@@ -170,7 +165,7 @@ data ArgumentDefinition = ArgumentDefinition Name (AnnotatedType InputType) (May
170165
instance HasName ArgumentDefinition where
171166
getName (ArgumentDefinition name _ _) = name
172167

173-
data InterfaceTypeDefinition = InterfaceTypeDefinition Name (NonEmptyList FieldDefinition)
168+
data InterfaceTypeDefinition = InterfaceTypeDefinition Name (NonEmpty FieldDefinition)
174169
deriving (Eq, Ord, Show)
175170

176171
instance HasName InterfaceTypeDefinition where
@@ -179,7 +174,7 @@ instance HasName InterfaceTypeDefinition where
179174
instance DefinesTypes InterfaceTypeDefinition where
180175
getDefinedTypes i@(InterfaceTypeDefinition name fields) = Map.singleton name (TypeDefinitionInterface i) <> foldMap getDefinedTypes fields
181176

182-
data UnionTypeDefinition = UnionTypeDefinition Name (NonEmptyList ObjectTypeDefinition)
177+
data UnionTypeDefinition = UnionTypeDefinition Name (NonEmpty ObjectTypeDefinition)
183178
deriving (Eq, Ord, Show)
184179

185180
instance HasName UnionTypeDefinition where
@@ -237,7 +232,7 @@ newtype EnumValueDefinition = EnumValueDefinition Name
237232
instance HasName EnumValueDefinition where
238233
getName (EnumValueDefinition name) = name
239234

240-
data InputObjectTypeDefinition = InputObjectTypeDefinition Name (NonEmptyList InputObjectFieldDefinition)
235+
data InputObjectTypeDefinition = InputObjectTypeDefinition Name (NonEmpty InputObjectFieldDefinition)
241236
deriving (Eq, Ord, Show)
242237

243238
instance HasName InputObjectTypeDefinition where
@@ -305,4 +300,4 @@ doesFragmentTypeApply objectType fragmentType =
305300
_ -> False
306301
where
307302
implements (ObjectTypeDefinition _ interfaces _) int = int `elem` interfaces
308-
branchOf obj (UnionTypeDefinition _ (NonEmptyList branches)) = obj `elem` branches
303+
branchOf obj (UnionTypeDefinition _ branches) = obj `elem` branches

0 commit comments

Comments
 (0)