Skip to content

Commit dfcd95a

Browse files
authored
Merge pull request #92 from jml/selection-set-2
Merge selections in a set into ordered map of fields
2 parents 7ea27af + 5b8be19 commit dfcd95a

File tree

12 files changed

+642
-280
lines changed

12 files changed

+642
-280
lines changed

HLint.hs

+1
Original file line numberDiff line numberDiff line change
@@ -3,3 +3,4 @@ import "hint" HLint.Generalise
33

44
ignore "Use fmap"
55
ignore "Redundant do"
6+
ignore "Use =<<"

graphql-wai/src/GraphQL/Wai.hs

+5-1
Original file line numberDiff line numberDiff line change
@@ -2,13 +2,15 @@
22
{-# LANGUAGE FlexibleContexts #-}
33
{-# LANGUAGE ScopedTypeVariables #-}
44

5+
-- | Basic WAI handlers for graphql-api
56
module GraphQL.Wai
67
( toApplication
78
) where
89

910
import Protolude
1011

1112
import GraphQL (interpretAnonymousQuery)
13+
import GraphQL.API (HasObjectDefinition)
1214
import GraphQL.Resolver (HasResolver, Handler)
1315
import Network.Wai (Application, queryString, responseLBS)
1416
import GraphQL.Value.ToValue (toValue)
@@ -23,7 +25,9 @@ import qualified Data.Aeson as Aeson
2325
--
2426
-- If you have a 'Cat' type and a corresponding 'catHandler' then you
2527
-- can use "toApplication @Cat catHandler".
26-
toApplication :: forall r. (HasResolver IO r) => Handler IO r -> Application
28+
toApplication
29+
:: forall r. (HasResolver IO r, HasObjectDefinition r)
30+
=> Handler IO r -> Application
2731
toApplication handler = app
2832
where
2933
app req respond =

src/GraphQL.hs

+36-25
Original file line numberDiff line numberDiff line change
@@ -7,21 +7,27 @@
77
-- __Note__: This module is highly subject to change. We're still figuring
88
-- where to draw the lines and what to expose.
99
module GraphQL
10-
( QueryError
10+
(
11+
-- * Running queries
12+
interpretQuery
13+
, interpretAnonymousQuery
1114
, Response(..)
12-
, VariableValues
13-
, Value
15+
-- * Preparing queries then running them
16+
, makeSchema
1417
, compileQuery
1518
, executeQuery
16-
, interpretQuery
17-
, interpretAnonymousQuery
19+
, QueryError
20+
, Schema
21+
, VariableValues
22+
, Value
1823
) where
1924

2025
import Protolude
2126

2227
import Data.Attoparsec.Text (parseOnly, endOfInput)
2328
import Data.List.NonEmpty (NonEmpty(..))
2429
import qualified Data.List.NonEmpty as NonEmpty
30+
import GraphQL.API (HasObjectDefinition(..))
2531
import GraphQL.Internal.Execution
2632
( VariableValues
2733
, ExecutionError
@@ -32,20 +38,21 @@ import qualified GraphQL.Internal.Syntax.AST as AST
3238
import qualified GraphQL.Internal.Syntax.Parser as Parser
3339
import GraphQL.Internal.Validation
3440
( QueryDocument
35-
, SelectionSet
41+
, SelectionSetByType
3642
, ValidationErrors
3743
, validate
3844
, getSelectionSet
3945
, VariableValue
4046
)
4147
import GraphQL.Internal.Output
4248
( GraphQLError(..)
43-
, Error(..)
4449
, Response(..)
4550
, singleError
4651
)
52+
import GraphQL.Internal.Schema (Schema)
53+
import qualified GraphQL.Internal.Schema as Schema
4754
import GraphQL.Resolver (HasResolver(..), Result(..))
48-
import GraphQL.Value (Name, Value, pattern ValueObject)
55+
import GraphQL.Value (Name, NameError, Value, pattern ValueObject)
4956

5057
-- | Errors that can happen while processing a query document.
5158
data QueryError
@@ -58,6 +65,8 @@ data QueryError
5865
| ValidationError ValidationErrors
5966
-- | Validated, but failed during execution.
6067
| ExecutionError ExecutionError
68+
-- | Error in the schema.
69+
| SchemaError NameError
6170
-- | Got a value that wasn't an object.
6271
| NonObjectResult Value
6372
deriving (Eq, Show)
@@ -69,12 +78,14 @@ instance GraphQLError QueryError where
6978
"Validation errors:\n" <> mconcat [" " <> formatError e <> "\n" | e <- NonEmpty.toList es]
7079
formatError (ExecutionError e) =
7180
"Execution error: " <> show e
81+
formatError (SchemaError e) =
82+
"Schema error: " <> formatError e
7283
formatError (NonObjectResult v) =
7384
"Query returned a value that is not an object: " <> show v
7485

7586
-- | Execute a GraphQL query.
7687
executeQuery
77-
:: forall api m. (HasResolver m api, Applicative m)
88+
:: forall api m. (HasResolver m api, Applicative m, HasObjectDefinition api)
7889
=> Handler m api -- ^ Handler for the query. This links the query to the code you've written to handle it.
7990
-> QueryDocument VariableValue -- ^ A validated query document. Build one with 'compileQuery'.
8091
-> Maybe Name -- ^ An optional name. If 'Nothing', then executes the only operation in the query. If @Just "something"@, executes the query named @"something".
@@ -83,59 +94,59 @@ executeQuery
8394
executeQuery handler document name variables =
8495
case getOperation document name variables of
8596
Left e -> pure (ExecutionFailure (singleError e))
86-
Right operation -> toResult <$> resolve @m @api handler operation
97+
Right operation -> toResult <$> resolve @m @api handler (Just operation)
8798
where
8899
toResult (Result errors result) =
89100
case result of
90-
-- TODO: Prevent this at compile time.
101+
-- TODO: Prevent this at compile time. Particularly frustrating since
102+
-- we *know* that api has an object definition.
91103
ValueObject object ->
92104
case NonEmpty.nonEmpty errors of
93105
Nothing -> Success object
94106
Just errs -> PartialSuccess object (map toError errs)
95107
v -> ExecutionFailure (singleError (NonObjectResult v))
96108

109+
-- | Create a GraphQL schema.
110+
makeSchema :: forall api. HasObjectDefinition api => Either QueryError Schema
111+
makeSchema = first SchemaError (Schema.makeSchema <$> getDefinition @api)
112+
97113
-- | Interpet a GraphQL query.
98114
--
99115
-- Compiles then executes a GraphQL query.
100116
interpretQuery
101-
:: forall api m. (Applicative m, HasResolver m api)
117+
:: forall api m. (Applicative m, HasResolver m api, HasObjectDefinition api)
102118
=> Handler m api -- ^ Handler for the query. This links the query to the code you've written to handle it.
103119
-> Text -- ^ The text of a query document. Will be parsed and then executed.
104120
-> 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"@.
105121
-> VariableValues -- ^ Values for variables defined in the query document. A map of 'Variable' to 'Value'.
106122
-> m Response -- ^ The outcome of running the query.
107123
interpretQuery handler query name variables =
108-
case parseQuery query of
109-
Left err -> pure (PreExecutionFailure (Error err [] :| []))
110-
Right parsed ->
111-
case validate parsed of
112-
Left errs -> pure (PreExecutionFailure (map toError errs))
113-
Right document ->
114-
executeQuery @api @m handler document name variables
115-
124+
case makeSchema @api >>= flip compileQuery query of
125+
Left err -> pure (PreExecutionFailure (toError err :| []))
126+
Right document -> executeQuery @api @m handler document name variables
116127

117128
-- | Interpret an anonymous GraphQL query.
118129
--
119130
-- Anonymous queries have no name and take no variables.
120131
interpretAnonymousQuery
121-
:: forall api m. (Applicative m, HasResolver m api)
132+
:: forall api m. (Applicative m, HasResolver m api, HasObjectDefinition api)
122133
=> Handler m api -- ^ Handler for the anonymous query.
123134
-> Text -- ^ The text of the anonymous query. Should defined only a single, unnamed query operation.
124135
-> m Response -- ^ The result of running the query.
125136
interpretAnonymousQuery handler query = interpretQuery @api @m handler query Nothing mempty
126137

127138
-- | Turn some text into a valid query document.
128-
compileQuery :: Text -> Either QueryError (QueryDocument VariableValue)
129-
compileQuery query = do
139+
compileQuery :: Schema -> Text -> Either QueryError (QueryDocument VariableValue)
140+
compileQuery schema query = do
130141
parsed <- first ParseError (parseQuery query)
131-
first ValidationError (validate parsed)
142+
first ValidationError (validate schema parsed)
132143

133144
-- | Parse a query document.
134145
parseQuery :: Text -> Either Text AST.QueryDocument
135146
parseQuery query = first toS (parseOnly (Parser.queryDocument <* endOfInput) query)
136147

137148
-- | Get an operation from a query document ready to be processed.
138-
getOperation :: QueryDocument VariableValue -> Maybe Name -> VariableValues -> Either QueryError (SelectionSet Value)
149+
getOperation :: QueryDocument VariableValue -> Maybe Name -> VariableValues -> Either QueryError (SelectionSetByType Value)
139150
getOperation document name vars = first ExecutionError $ do
140151
op <- Execution.getOperation document name
141152
resolved <- substituteVariables op vars

src/GraphQL/Internal/OrderedMap.hs

+62-1
Original file line numberDiff line numberDiff line change
@@ -36,9 +36,15 @@ module GraphQL.Internal.OrderedMap
3636
, orderedMap
3737
-- * Querying
3838
, lookup
39+
-- * Filtering
40+
, GraphQL.Internal.OrderedMap.catMaybes
3941
-- * Combine
4042
-- ** Union
4143
, unions
44+
, unionWith
45+
, unionsWith
46+
, unionWithM
47+
, unionsWithM
4248
-- * Conversion
4349
, toList
4450
, toMap
@@ -69,7 +75,7 @@ data OrderedMap key value
6975
--
7076
-- /O(n log n)/
7177
toList :: forall key value. Ord key => OrderedMap key value -> [(key, value)]
72-
toList (OrderedMap keys entries) = catMaybes (foreach keys $ \k -> (,) k <$> Map.lookup k entries)
78+
toList (OrderedMap keys entries) = Protolude.catMaybes (foreach keys $ \k -> (,) k <$> Map.lookup k entries)
7379

7480
instance Foldable (OrderedMap key) where
7581
foldr f z (OrderedMap _ entries) = foldr f z entries
@@ -120,6 +126,61 @@ values = map snd . toList
120126
unions :: forall key value. Ord key => [OrderedMap key value] -> Maybe (OrderedMap key value)
121127
unions orderedMaps = orderedMap (orderedMaps >>= toList)
122128

129+
-- | Append the second ordered map to the first, combining any shared elements
130+
-- with the given function.
131+
unionWith :: Ord key
132+
=> (value -> value -> value)
133+
-> OrderedMap key value
134+
-> OrderedMap key value
135+
-> OrderedMap key value
136+
unionWith f x y =
137+
OrderedMap
138+
{ toMap = Map.unionWith f (toMap x) (toMap y)
139+
, keys = keys x <> [k | k <- keys y, k `Map.notMember` toMap x]
140+
}
141+
142+
-- | Append together a list of ordered maps, preserving ordering of keys.
143+
-- Combine any shared elements with the given function.
144+
unionsWith :: Ord key
145+
=> (value -> value -> value)
146+
-> [OrderedMap key value]
147+
-> OrderedMap key value
148+
unionsWith f = foldl' (unionWith f) empty
149+
150+
-- | Take two ordered maps, append the second one to the first. If the second
151+
-- contains any keys that also appear in the first, combine the two values
152+
-- with the given function.
153+
unionWithM :: (Monad m, Ord key)
154+
=> (value -> value -> m value)
155+
-> OrderedMap key value
156+
-> OrderedMap key value
157+
-> m (OrderedMap key value)
158+
unionWithM f x y = sequenceA (unionWith (liftMM f) (map pure x) (map pure y))
159+
160+
-- | Take a list of ordered maps and append them together. Any shared elements
161+
-- are combined using the given function.
162+
unionsWithM :: (Monad m, Ord key)
163+
=> (value -> value -> m value)
164+
-> [OrderedMap key value]
165+
-> m (OrderedMap key value)
166+
unionsWithM f xs = sequenceA (unionsWith (liftMM f) (map (map pure) xs))
167+
168+
liftMM :: Monad m => (a -> b -> m c) -> m a -> m b -> m c
169+
liftMM f a' b' = do
170+
(a, b) <- (,) <$> a' <*> b'
171+
f a b
172+
173+
-- | Take an ordered map with 'Maybe' values and return the same map with all
174+
-- the 'Nothing' values removed.
175+
catMaybes :: Ord key => OrderedMap key (Maybe value) -> OrderedMap key value
176+
catMaybes xs =
177+
OrderedMap
178+
{ keys = [ k | k <- keys xs, k `Map.member` newMap ]
179+
, toMap = newMap
180+
}
181+
where
182+
newMap = Map.mapMaybe identity (toMap xs)
183+
123184
-- | Construct an ordered map from a list.
124185
--
125186
-- /O(n log n)/.

0 commit comments

Comments
 (0)