Skip to content

Commit 6c4a6f4

Browse files
authored
Merge pull request #87 from jml/71-rename-build-resolver
Rename buildResolver
2 parents 207a2ff + dc81779 commit 6c4a6f4

File tree

2 files changed

+37
-52
lines changed

2 files changed

+37
-52
lines changed

src/GraphQL.hs

Lines changed: 5 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -44,7 +44,7 @@ import GraphQL.Internal.Output
4444
, Response(..)
4545
, singleError
4646
)
47-
import GraphQL.Resolver (HasGraph(..), Result(..))
47+
import GraphQL.Resolver (HasResolver(..), Result(..))
4848
import GraphQL.Value (Name, Value, pattern ValueObject)
4949

5050
-- | Errors that can happen while processing a query document.
@@ -74,7 +74,7 @@ instance GraphQLError QueryError where
7474

7575
-- | Execute a GraphQL query.
7676
executeQuery
77-
:: forall api m. (HasGraph m api, Applicative m)
77+
:: forall api m. (HasResolver m api, Applicative m)
7878
=> Handler m api -- ^ Handler for the query. This links the query to the code you've written to handle it.
7979
-> QueryDocument VariableValue -- ^ A validated query document. Build one with 'compileQuery'.
8080
-> Maybe Name -- ^ An optional name. If 'Nothing', then executes the only operation in the query. If @Just "something"@, executes the query named @"something".
@@ -83,8 +83,7 @@ executeQuery
8383
executeQuery handler document name variables =
8484
case getOperation document name variables of
8585
Left e -> pure (ExecutionFailure (singleError e))
86-
Right operation ->
87-
toResult <$> buildResolver @m @api handler operation
86+
Right operation -> toResult <$> resolve @m @api handler operation
8887
where
8988
toResult (Result errors result) =
9089
case result of
@@ -99,7 +98,7 @@ executeQuery handler document name variables =
9998
--
10099
-- Compiles then executes a GraphQL query.
101100
interpretQuery
102-
:: forall api m. (Applicative m, HasGraph m api)
101+
:: forall api m. (Applicative m, HasResolver m api)
103102
=> Handler m api -- ^ Handler for the query. This links the query to the code you've written to handle it.
104103
-> Text -- ^ The text of a query document. Will be parsed and then executed.
105104
-> Maybe Name -- ^ An optional name for the operation within document to run. If 'Nothing', execute the only operation in the document. If @Just "something"@, execute the query or mutation named @"something"@.
@@ -119,7 +118,7 @@ interpretQuery handler query name variables =
119118
--
120119
-- Anonymous queries have no name and take no variables.
121120
interpretAnonymousQuery
122-
:: forall api m. (Applicative m, HasGraph m api)
121+
:: forall api m. (Applicative m, HasResolver m api)
123122
=> Handler m api -- ^ Handler for the anonymous query.
124123
-> Text -- ^ The text of the anonymous query. Should defined only a single, unnamed query operation.
125124
-> m Response -- ^ The result of running the query.

src/GraphQL/Resolver.hs

Lines changed: 32 additions & 46 deletions
Original file line numberDiff line numberDiff line change
@@ -14,10 +14,9 @@
1414
{-# LANGUAGE UndecidableInstances #-} -- for TypeError
1515

1616
module GraphQL.Resolver
17-
( ResolverError(..) -- XXX: Exporting constructor for tests. Not sure if that's what we really want.
18-
, HasGraph(..)
17+
( ResolverError(..)
18+
, HasResolver(..)
1919
, (:<>)(..)
20-
, BuildFieldResolver(..)
2120
, Defaultable(..)
2221
, Result(..)
2322
, unionValue
@@ -143,9 +142,9 @@ ok :: Value -> Result Value
143142
ok = pure
144143

145144

146-
class HasGraph m a where
145+
class HasResolver m a where
147146
type Handler m a
148-
buildResolver :: Handler m a -> SelectionSet Value -> m (Result Value)
147+
resolve :: Handler m a -> SelectionSet Value -> m (Result Value)
149148

150149
-- | Specify a default value for a type in a GraphQL schema.
151150
--
@@ -180,62 +179,49 @@ instance Defaultable (Maybe a) where
180179
-- | The default for @Maybe a@ is @Nothing@.
181180
defaultFor _ = pure Nothing
182181

183-
instance forall m. (Functor m) => HasGraph m Int32 where
182+
instance forall m. (Functor m) => HasResolver m Int32 where
184183
type Handler m Int32 = m Int32
185184
-- TODO check that selectionset is empty (we expect a terminal node)
186-
buildResolver handler _ = do
185+
resolve handler _ = do
187186
map (ok . toValue) handler
188187

189188

190-
instance forall m. (Functor m) => HasGraph m Double where
189+
instance forall m. (Functor m) => HasResolver m Double where
191190
type Handler m Double = m Double
192191
-- TODO check that selectionset is empty (we expect a terminal node)
193-
buildResolver handler _ = map (ok . toValue) handler
192+
resolve handler _ = map (ok . toValue) handler
194193

195-
instance forall m. (Functor m) => HasGraph m Text where
194+
instance forall m. (Functor m) => HasResolver m Text where
196195
type Handler m Text = m Text
197196
-- TODO check that selectionset is empty (we expect a terminal node)
198-
buildResolver handler _ = map (ok . toValue) handler
197+
resolve handler _ = map (ok . toValue) handler
199198

200-
instance forall m. (Functor m) => HasGraph m Bool where
199+
instance forall m. (Functor m) => HasResolver m Bool where
201200
type Handler m Bool = m Bool
202201
-- TODO check that selectionset is empty (we expect a terminal node)
203-
buildResolver handler _ = map (ok . toValue) handler
202+
resolve handler _ = map (ok . toValue) handler
204203

205-
instance forall m hg. (HasGraph m hg, Functor m, ToValue (Maybe hg)) => HasGraph m (Maybe hg) where
204+
instance forall m hg. (HasResolver m hg, Functor m, ToValue (Maybe hg)) => HasResolver m (Maybe hg) where
206205
type Handler m (Maybe hg) = m (Maybe hg)
207-
buildResolver handler _ = map (ok . toValue) handler
206+
resolve handler _ = map (ok . toValue) handler
208207

209-
instance forall m hg. (Monad m, Applicative m, HasGraph m hg) => HasGraph m (API.List hg) where
208+
instance forall m hg. (Monad m, Applicative m, HasResolver m hg) => HasResolver m (API.List hg) where
210209
type Handler m (API.List hg) = m [Handler m hg]
211-
buildResolver handler selectionSet = do
210+
resolve handler selectionSet = do
212211
h <- handler
213-
let a = traverse (flip (buildResolver @m @hg) selectionSet) h
212+
let a = traverse (flip (resolve @m @hg) selectionSet) h
214213
map aggregateResults a
215214

216215

217-
instance forall m ksN enum. (Applicative m, API.GraphQLEnum enum) => HasGraph m (API.Enum ksN enum) where
216+
instance forall m ksN enum. (Applicative m, API.GraphQLEnum enum) => HasResolver m (API.Enum ksN enum) where
218217
type Handler m (API.Enum ksN enum) = enum
219-
buildResolver handler _ = (pure . ok . GValue.ValueEnum . API.enumToValue) handler
218+
resolve handler _ = (pure . ok . GValue.ValueEnum . API.enumToValue) handler
220219

221-
222-
-- TODO: variables should error, they should have been resolved already.
223-
--
224-
-- TODO: Objects. Maybe implement some Generic object reader? I.e. if I do
225-
-- data Greet = Greet { name :: Text, score :: Int } deriving Generic
226-
-- then "instance ReadValue Greet" would fall back on a default reader that
227-
-- expects Objects?
228-
-- Maybe we can use advanced fallbacks like these:
229-
-- https://wiki.haskell.org/GHC/AdvancedOverlap
230-
231-
232-
-- Iterate through handlers (zipped together with their type
233-
-- definition) and execute handler if the name matches.
234-
235-
-- TODO: A parametrized `Result` is really not a good way to handle
236-
-- the "result" for resolveField, but not sure what to use either. I
237-
-- liked the tuple we had before more because it didn't imply any
238-
-- other structure or meaning. Maybe we can jsut create a new datatype.
220+
-- TODO: A parametrized `Result` is really not a good way to handle the
221+
-- "result" for resolveField, but not sure what to use either. Tom liked the
222+
-- tuple we had before more because it didn't imply any other structure or
223+
-- meaning. Maybe we can just create a new datatype. jml thinks we should
224+
-- extract some helpful generic monad, ala `Validator`.
239225
type ResolveFieldResult = Result (Maybe GValue.ObjectField)
240226

241227
-- Extract field name from an argument type. TODO: ideally we'd run
@@ -291,10 +277,10 @@ class BuildFieldResolver m fieldResolverType where
291277
buildFieldResolver :: FieldHandler m fieldResolverType -> Field Value -> Either ResolverError (m (Result Value))
292278

293279
instance forall ksG t m.
294-
( KnownSymbol ksG, HasGraph m t, HasAnnotatedType t, Monad m
280+
( KnownSymbol ksG, HasResolver m t, HasAnnotatedType t, Monad m
295281
) => BuildFieldResolver m (JustHandler (API.Field ksG t)) where
296282
buildFieldResolver handler field = do
297-
let resolver = buildResolver @m @t handler (getFieldSelectionSet field)
283+
let resolver = resolve @m @t handler (getFieldSelectionSet field)
298284
pure resolver
299285

300286
instance forall ksH t f m.
@@ -401,10 +387,10 @@ instance forall m a b dispatchType.
401387
instance forall typeName interfaces fields m.
402388
( RunFields m (RunFieldsType m fields)
403389
, Monad m
404-
) => HasGraph m (API.Object typeName interfaces fields) where
390+
) => HasResolver m (API.Object typeName interfaces fields) where
405391
type Handler m (API.Object typeName interfaces fields) = m (RunFieldsHandler m (RunFieldsType m fields))
406392

407-
buildResolver mHandler selectionSet = do
393+
resolve mHandler selectionSet = do
408394
-- First we run the actual handler function itself in IO.
409395
handler <- mHandler
410396
let fields = getFields selectionSet
@@ -425,7 +411,7 @@ instance forall typeName interfaces fields m.
425411
-- | For unions we need a way to have type-safe, open sum types based
426412
-- on the possible 'API.Object's of a union. The following closed type
427413
-- family selects one Object from the union and returns the matching
428-
-- 'HasGraph' 'Handler' type. If the object @o@ is not a member of
414+
-- 'HasResolver' 'Handler' type. If the object @o@ is not a member of
429415
-- 'API.Union' then the user code won't compile.
430416
--
431417
-- This type family is an implementation detail but its TypeError
@@ -465,7 +451,7 @@ instance forall m union objects name interfaces fields.
465451
) => RunUnion m union (API.Object name interfaces fields:objects) where
466452
runUnion duv fragment@(InlineFragment _ _ selection) =
467453
case extractUnionValue @(API.Object name interfaces fields) @union @m duv of
468-
Just handler -> buildResolver @m @(API.Object name interfaces fields) handler selection
454+
Just handler -> resolve @m @(API.Object name interfaces fields) handler selection
469455
Nothing -> runUnion @m @union @objects duv fragment
470456

471457
-- AFAICT it should not be possible to ever hit the empty case because
@@ -483,11 +469,11 @@ instance forall m unionName objects.
483469
( Monad m
484470
, KnownSymbol unionName
485471
, RunUnion m (API.Union unionName objects) objects
486-
) => HasGraph m (API.Union unionName objects) where
472+
) => HasResolver m (API.Union unionName objects) where
487473
type Handler m (API.Union unionName objects) = m (DynamicUnionValue (API.Union unionName objects) m)
488474
-- 'label' is the name of the GraphQL type of the branch of the union that
489475
-- we are currently implementing.
490-
buildResolver mHandler selectionSet = do
476+
resolve mHandler selectionSet = do
491477
duv@(DynamicUnionValue label _) <- mHandler
492478
case makeName label of
493479
Left e -> pure (Result [SchemaError e] GValue.ValueNull)

0 commit comments

Comments
 (0)