@@ -6,58 +6,304 @@ First some imports:
66{-# LANGUAGE DataKinds #-}
77{-# LANGUAGE TypeOperators #-}
88{-# LANGUAGE OverloadedStrings #-}
9+ {-# LANGUAGE TypeApplications #-}
10+
911module Introduction where
1012
1113import Protolude
1214
13- import GraphQL.API (Object, Field, Argument, (:>))
14- import GraphQL.Resolver (Handler, (:<>)(..))
15+ import System.Random
16+
17+ import GraphQL
18+ import GraphQL.API (Object, Field, Argument, (:>), Union)
19+ import GraphQL.Resolver (Handler, (:<>)(..), unionValue)
20+ `` `
21+
22+ ## A simple GraphQL service
23+
24+ A [GraphQL](http://graphql.org/) service is made up of two things:
25+
26+ 1. A schema that defines the service
27+ 2. Some code that implements the service's behavior
28+
29+ We're going to build a very simple service that says hello to
30+ people. Our GraphQL schema for this looks like:
31+
32+ `` `graphql
33+ type Hello {
34+ greeting(who: String!): String!
35+ }
36+ `` `
37+
38+ Which means we have base type, an _object_ called `Hello`, which has a single
39+ _field_ `greeting`, which takes a non-nullable `String` called `who` and
40+ returns a `String`.
41+
42+ Note that all the types here are GraphQL types, not Haskell types. `String`
43+ here is a GraphQL `String`, not a Haskell one.
44+
45+ And we want to be able to send queries that look like:
46+
47+ `` `graphql
48+ {
49+ greeting(who: "world" )
50+ }
51+ `` `
52+
53+ And get responses like:
54+
55+ `` `json
56+ {
57+ "data" : {
58+ "greeting" : "Hello world!"
59+ }
60+ }
61+ `` `
62+
63+ ### Defining the schema
64+
65+ Here's how we would define the schema in Haskell:
66+
67+ `` `haskell
68+ type Hello = Object " Hello" '[]
69+ '[ Argument " who" Text :> Field " greeting" Text
70+ ]
71+ `` `
72+
73+ Breaking this down, we define a new Haskell type `Hello`, which is a GraphQL
74+ object (also named `" Hello" `) that implements no interfaces (hence `'[]`). It
75+ has one field, called `" greeting" ` which returns some `Text` and takes a
76+ single named argument `"who"` , which is also `Text`.
77+
78+ Note that the GraphQL `String` from above got translated into a Haskell
79+ `Text`.
80+
81+ There are some noteworthy differences between this schema and the GraphQL
82+ schema:
83+
84+ * The GraphQL schema requires a special annotation to say that a value cannot
85+ be null, `!`. In Haskell, we instead assume that nothing can be null.
86+ * In the GraphQL schema, the argument appears *after* the field name. In
87+ Haskell, it appears *before*.
88+ * In Haskell, we name the top-level type twice, once on left hand side of the
89+ type definition and once on the right.
90+
91+ ### Implementing the handlers
92+
93+ Once we have the schema, we need to define the corresponding handlers, which
94+ are `Handler` values.
95+
96+ Here's a `Handler` for `Hello`:
97+
98+ `` `haskell
99+ hello :: Handler IO Hello
100+ hello = pure greeting
101+ where
102+ greeting who = pure (" Hello " <> who <> " !")
103+ `` `
104+
105+ The type signature, `Handler IO Hello` shows that it's a `Handler` for
106+ `Hello`, and that it runs in the `IO` monad. (Note: nothing about this example
107+ code requires the `IO` monad, it's just a monad that lots of people has heard
108+ of.)
109+
110+ The implementation looks slightly weird, but it's weird for good reasons.
111+
112+ The first layer of the handler, `pure greeting`, produces the `Hello` object.
113+ The `pure` might seem redundant here, but making this step monadic allows us
114+ to run actions in the base monad.
115+
116+ The second layer of the handler, the implementation of `greeting`, produces
117+ the value of the `greeting` field. It is monadic so that it will only be
118+ executed when the field was requested.
119+
120+ Each field handler is a separate monadic action so we only perform the side
121+ effects for fields present in the query.
122+
123+ This handler is in `Identity` because it doesn't do anything particularly
124+ monadic. It could be in `IO` or `STM` or `ExceptT Text IO` or whatever you
125+ would like.
126+
127+ ### Running queries
128+
129+ Defining a service isn't much point unless you can query. Here's how:
130+
131+ `` `haskell
132+ queryHello :: IO Response
133+ queryHello = interpretAnonymousQuery @Hello hello " { greeting(who: \" mort\" ) }"
134+ `` `
135+
136+ The actual `Response` type is fairly verbose, so we're most likely to turn it
137+ into JSON:
138+
139+ `` `
140+ λ Aeson.encode <$ > queryHello
141+ "{\" greeting\" :\" Hello mort!\" }"
15142```
16143
17- The core idea for this library is that we define a composite type that
18- specifies the whole API, and then implement a matching handler.
144+ ## Combining field handlers with :<>
19145
20- The main GraphQL entities we care about are Objects and Fields. Each
21- Field can have arguments.
146+ How do we define an object with more than one field?
147+
148+ Let's implement a simple calculator that can add and subtract integers. First,
149+ the schema:
150+
151+ ```graphql
152+ type Calculator {
153+ add(a: Int!, b: Int!): Int!,
154+ sub(a: Int!, b: Int!): Int!,
155+ }
156+ ```
157+
158+ Here, `Calculator` is an object with two fields: `add` and `sub`.
159+
160+ And now the Haskell version:
22161
23162``` haskell
24- type HelloWorld = Object " HelloWorld" '[]
25- '[ Argument " greeting" Text :> Field "me" Text
163+ type Calculator = Object "Calculator" '[]
164+ '[ Argument "a" Int32 :> Argument "b" Int32 :> Field "add" Int32
165+ , Argument "a" Int32 :> Argument "b" Int32 :> Field "subtract" Int32
26166 ]
27167```
28168
29- The example above is equivalent to the following GraphQL type:
169+ So far, this is the same as our `Hello` example.
170+
171+ And its handler:
30172
173+ ```haskell
174+ calculator :: Handler IO Calculator
175+ calculator = pure (add :<> subtract')
176+ where
177+ add a b = pure (a + b)
178+ subtract' a b = pure (a - b)
31179```
32- type HelloWorld {
33- me(greeting: String!): String!
180+
181+ This handler introduces a new operator, `:<>` (pronounced "birdface"), which
182+ is used to compose two existing handlers into a new handler. It's inspired by
183+ the operator for monoids, `<>`.
184+
185+ Note that we still need `pure` for each individual handler.
186+
187+ ## Nesting Objects
188+
189+ How do we define objects made up other objects?
190+
191+ One of the great things in GraphQL is that objects can be used as types for
192+ fields. Take this classic GraphQL schema as an example:
193+
194+ ```graphql
195+ type Query {
196+ me: User!
197+ }
198+
199+ type User {
200+ name: Text!
201+ }
202+ ```
203+
204+ We would query this schema with something like:
205+
206+ ```graphql
207+ {
208+ me {
209+ name
210+ }
34211}
35212```
36213
37- And if we had a code to handle that type (more later) we could query it like this :
214+ Which would produce output like:
38215
216+ ```json
217+ {
218+ "data" : {
219+ "me" : {
220+ "name" : "Mort"
221+ }
222+ }
223+ }
39224```
40- { me(greeting: "hello" ) }
225+
226+ The Haskell type for this schema looks like:
227+
228+ ```haskell
229+ type User = Object "User" '[] '[Field "name" Text]
230+ type Query = Object "Query" '[] '[Field "me" User]
41231```
42232
43- ## The handler
233+ Note that `Query` refers to the type `User` when it defines the field `me`.
44234
45- We defined a corresponding handler via the `Handler m a` which takes
46- the monad to run in (`IO` in this case) and the actual API definition
47- (`HelloWorld`).
235+ We write nested handlers the same way we write the top-level handler:
48236
49237```haskell
50- handler :: Handler IO HelloWorld
51- handler = pure (\greeting -> pure (greeting <> " to me" ))
238+ user :: Handler IO User
239+ user = pure name
240+ where
241+ name = pure "Mort"
242+
243+ query :: Handler IO Query
244+ query = pure user
52245```
53246
54- The implementation looks slightly weird, but it's weird for good
55- reasons. In order:
247+ And that's it.
56248
57- * The first `pure` allows us to run actions in the base monad (`IO`
58- here) before returning anything. This is useful to allocate a resource
59- like a database connection.
60- * The `pure` in the function call allows us to **avoid running
61- actions** when the field hasn't been requested: Each handler is a
62- separate monadic action so we only perform the side effects for fields
63- present in the query.
249+ ## Unions
250+
251+ GraphQL has [support for union
252+ types](http://graphql.org/learn/schema/#union-types). These require special
253+ treatment in Haskell.
254+
255+ Let's define a union, first in GraphQL:
256+
257+ ```graphql
258+ union UserOrCalculator = User | Calculator
259+ ```
260+
261+ And now in Haskell:
262+
263+ ```haskell
264+ type UserOrCalculator = Union "UserOrCalculator" '[User, Calculator]
265+ ```
266+
267+ And let's define a very simple top-level object that uses `UserOrCalculator`:
268+
269+ ```haskell
270+ type UnionQuery = Object "UnionQuery" '[] '[Field "union" UserOrCalculator]
271+ ```
272+
273+ and a handler that randomly returns either a user or a calculator:
274+
275+ ```haskell
276+ unionQuery :: Handler IO UnionQuery
277+ unionQuery = do
278+ returnUser <- randomIO
279+ if returnUser
280+ then pure (unionValue @User user)
281+ else pure (unionValue @Calculator calculator)
282+ ```
283+
284+ The important thing here is that we have to wrap the actual objects we return
285+ using `unionValue`.
286+
287+ Note that while `unionValue` looks a bit like `unsafeCoerce` by forcing one
288+ type to become another type, it's actually type-safe because we use a
289+ *type-index* to pick the correct type from the union. Using e.g. `unionValue
290+ @HelloWorld handler` will not compile because `HelloWorld` is not in the
291+ union.
292+
293+ ## Where next?
294+
295+ We have an
296+ [examples](https://github.com/jml/graphql-api/tree/master/tests/Examples)
297+ directory showing full code examples.
298+
299+ We also have a fair number of [end-to-end
300+ tests](https://github.com/jml/graphql-api/tree/master/tests/EndToEndTests.hs)
301+ based on an [example
302+ schema](https://github.com/jml/graphql-api/tree/master/tests/ExampleSchema.hs)
303+ that you might find interesting.
304+
305+ If you want to try the examples in this tutorial you can run:
306+
307+ ```bash
308+ stack repl tutorial
309+ ```
0 commit comments