@@ -12,63 +12,146 @@ module Introduction where
1212
1313import Protolude
1414
15+ import System.Random
16+
1517import GraphQL
1618import GraphQL.API (Object, Field, Argument, (:>), Union)
1719import GraphQL.Resolver (Handler, (:<>)(..), unionValue)
1820`` `
1921
20- The core idea for this library is that we define a composite type that
21- specifies the whole API, and then implement a matching handler.
22+ ## A simple GraphQL service
2223
23- The main GraphQL entities we care about are Objects and Fields. Each
24- Field can have arguments.
24+ A [GraphQL](http://graphql.org/) service is made up of two things:
2525
26- `` ` haskell
27- type HelloWorld = Object " HelloWorld" '[]
28- '[ Argument " greeting" Text :> Field "me" Text
29- ]
30- `` `
26+ 1. A schema that defines the service
27+ 2. Some code that implements the service's behavior
3128
32- The example above is equivalent to the following GraphQL type:
29+ We're going to build a very simple service that says hello to
30+ people. Our GraphQL schema for this looks like:
3331
32+ `` `graphql
33+ type Hello {
34+ greeting(who: String!): String!
35+ }
3436`` `
35- type HelloWorld {
36- me(greeting: String!): String!
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+ And we want to be able to send queries that look like:
43+
44+ `` `graphql
45+ {
46+ greeting(who: "world" )
3747}
3848`` `
3949
40- And if we had a code to handle that type (more later) we could query it like this :
50+ And get responses like:
4151
52+ `` `json
53+ {
54+ data: {
55+ greeting: "Hello world!"
56+ }
57+ }
4258`` `
43- { me(greeting: "hello" ) }
59+
60+ ### Defining the schema
61+
62+ Here's how we would define the schema in Haskell:
63+
64+ `` `haskell
65+ type Hello = Object " Hello" '[]
66+ '[ Argument " who" Text :> Field " greeting" Text
67+ ]
4468`` `
4569
46- ## Implementing a handler
70+ Breaking this down, we define a new Haskell type `Hello`, which is a GraphQL
71+ object (also named `" Hello" `) that implements no interfaces (hence `'[]`). It
72+ has one field, called `" greeting" ` which returns some `Text` and takes a
73+ single named argument `"who"` , which is also `Text`.
74+
75+ There are some noteworthy differences between this schema and the GraphQL
76+ schema:
77+
78+ * The GraphQL schema requires a special annotation to say that a value cannot
79+ be null, `!`. In Haskell, we instead assume that everything can't be null.
80+ * In the GraphQL schema, the argument appears *after* the field name. In
81+ Haskell, it appears *before*.
82+ * In Haskell, we name the top-level type twice, once on left hand side of the
83+ type definition and once on the right.
84+
85+ ### Implementing the handlers
86+
87+ Once we have the schema, we need to define the corresponding handlers, which
88+ are `Handler` values.
4789
48- We define a corresponding handler via the `Handler m a` which takes
49- the monad to run in (`IO` in this case) and the actual API definition
50- (`HelloWorld`):
90+ Here's a `Handler` for `Hello`:
5191
5292`` `haskell
53- handler :: Handler IO HelloWorld
54- handler = pure (\greeting -> pure (greeting <> " to me" ))
93+ hello :: Handler IO Hello
94+ hello = pure greeting
95+ where
96+ greeting who = pure (" Hello " <> who <> " !")
5597`` `
5698
57- The implementation looks slightly weird, but it's weird for good
58- reasons. In order:
99+ The type signature, `Handler IO Hello` shows that it's a `Handler` for
100+ `Hello`, and that it runs in the `IO` monad. (Note: nothing about this example
101+ code requires the `IO` monad, it's just a monad that lots of people has heard
102+ of.)
103+
104+ The implementation looks slightly weird, but it's weird for good reasons.
105+
106+ The first layer of the handler, `pure greeting`, produces the `Hello` object.
107+ The `pure` might seem redundant here, but making this step monadic allows us
108+ to run actions in the base monad.
109+
110+ The second layer of the handler, the implementation of `greeting`, produces
111+ the value of the `greeting` field. It is monadic so that it will only be
112+ executed when the field was requested.
113+
114+ Each handler is a separate monadic action so we only perform the side effects
115+ for fields present in the query.
59116
60- * The first `pure` allows us to run actions in the base monad (here `IO`
61- before returning anything. This is useful to allocate a resource
62- like a database connection.
63- * The `pure` in the function call allows us to **avoid running
64- actions** when the field hasn't been requested: Each handler is a
65- separate monadic action so we only perform the side effects for fields
66- present in the query.
117+ This handler is in `Identity` because it doesn't do anything particularly
118+ monadic. It could be in `IO` or `STM` or `ExceptT Text IO` or whatever you
119+ would like.
120+
121+ ### Running queries
122+
123+ Defining a service isn't much point unless you can query. Here's how:
124+
125+ `` `haskell
126+ queryHello :: IO Response
127+ queryHello = interpretAnonymousQuery @Hello hello " { greeting(who: \" mort\" ) }"
128+ `` `
67129
130+ The actual `Response` type is fairly big, so we're most likely to turn it into
131+ JSON:
132+
133+ `` `
134+ λ Aeson.encode <$ > queryHello
135+ "{\" greeting\" :\" Hello mort!\" }"
136+ ```
68137
69138## Combining field handlers with :<>
70139
71- Let's implement a simple calculator that can add and subtract integers:
140+ How do we define an object with more than one field?
141+
142+ Let's implement a simple calculator that can add and subtract integers. First,
143+ the schema:
144+
145+ ```graphql
146+ type Calculator {
147+ add(a: Int!, b: Int!): Int!,
148+ sub(a: Int!, b: Int!): Int!,
149+ }
150+ ```
151+
152+ Here, `Calculator` is an object with two fields: `add` and `sub`.
153+
154+ And now the Haskell version:
72155
73156``` haskell
74157type Calculator = Object "Calculator" '[]
@@ -77,107 +160,142 @@ type Calculator = Object "Calculator" '[]
77160 ]
78161```
79162
80- Every element in a list in Haskell has the same type, so we can't
81- really return a list of different handlers. Instead we compose the
82- different handlers with a new operator, `:<>`. This operator, commonly
83- called birdface, is based on the operator for monoids, `<>`.
163+ So far, this is the same as our `Hello` example.
84164
85- `` ` haskell
165+ And its handler:
166+
167+ ```haskell
86168calculator :: Handler IO Calculator
87169calculator = pure (add :<> subtract')
88170 where
89- add a b = pure (a + b)
90- subtract' a b = pure (a - b)
171+ add a b = pure (a + b)
172+ subtract' a b = pure (a - b)
91173```
92174
93- Note that we still need `pure` for each individual handler.
175+ This handler introduces a new operator, `:<>` (pronounced "birdface"), which
176+ is used to compose two existing handlers into a new handler. It's inspired by
177+ the operator for monoids, `<>`.
94178
179+ Note that we still need `pure` for each individual handler.
95180
96181## Nesting Objects
97182
98- Objects can be used as a type in fields. This allows us to implement a
99- server for the classic GraphQL example query:
183+ How do we define objects made up other objects?
100184
185+ One of the great things in GraphQL is that objects can be used as types for
186+ fields. Take this classic GraphQL schema as an example:
101187
188+ ```graphql
189+ type Query {
190+ me: User!
191+ }
192+
193+ type User {
194+ name: Text!
195+ }
102196```
197+
198+ We would query this schema with something like:
199+
200+ ```graphql
103201{
104- me { name }
202+ me {
203+ name
204+ }
105205}
106206```
107207
108- The Haskell schema for that looks like this :
208+ Which would produce output like:
109209
110- `` ` haskell
210+ ```json
211+ {
212+ data: {
213+ me: {
214+ name: "Mort"
215+ }
216+ }
217+ }
218+ ```
219+
220+ The Haskell type for this schema looks like:
221+
222+ ```haskell
111223type User = Object "User" '[] '[Field "name" Text]
112224type Query = Object "Query" '[] '[Field "me" User]
113225```
114226
115- Note the type `User` for `me`.
116-
227+ Note that `Query` refers to the type `User` when it defines the field `me`.
117228
118229We write nested handlers the same way we write the top-level handler:
119230
120- `` ` haskell
231+ ```haskell
121232user :: Handler IO User
122- user = pure (pure " mort" )
233+ user = pure name
234+ where
235+ name = pure "Mort"
123236
124237query :: Handler IO Query
125238query = pure user
126239```
127240
241+ And that's it.
242+
128243## Unions
129244
130- Union handlers require special treatment in Haskell because we need to
131- return the same type for each possible, different type in the union.
245+ GraphQL has [support for union
246+ types](http://graphql.org/learn/schema/#union-types). These require special
247+ treatment in Haskell.
132248
133- Let's define a union:
249+ Let's define a union, first in GraphQL :
134250
135- `` ` haskell
136- type UserOrCalcualtor = Union " UserOrCalcualtor" '[User, Calculator]
137- type UnionQuery = Object "UnionQuery" '[] ' [Field "union" UserOrCalcualtor]
251+ ```graphql
252+ union UserOrCalculator = User | Calculator
138253```
139254
140- and a handler that returns a user :
255+ And now in Haskell :
141256
142- `` ` haskell
143- unionQuery :: Handler IO UnionQuery
144- unionQuery = pure (unionValue @User user)
257+ ```haskell
258+ type UserOrCalcualtor = Union "UserOrCalcualtor" '[User, Calculator]
145259```
146260
147- Note that, while `unionValue` looks a bit like `unsafeCoerce` by
148- forcing one type to become another type, it's actually type-safe
149- because we use a *type-index* to pick the correct type from the
150- union. Using e.g. `unionValue @HelloWorld handler` will not compile
151- because `HelloWorld` is not in the union.
152-
153- ## Running a query
261+ And let's define a very simple top-level object that uses `UserOrCalcualtor`:
154262
155263```haskell
156- hello :: IO Response
157- hello = interpretAnonymousQuery @HelloWorld handler " { me(greeting: \" hey ho\" ) }"
264+ type UnionQuery = Object "UnionQuery" '[] '[Field "union" UserOrCalcualtor]
158265```
159266
160- But our output is pretty long :
267+ and a handler that randomly returns either a user or a calculator :
161268
162- `` `
163- λ hello
164- Success (Object' (OrderedMap {keys = [Name {unName = "me" }], toMap = fromList [(Name {unName = "me" },ValueScalar' (ConstString (String "hey ho to me" )))]}))
269+ ```haskell
270+ unionQuery :: Handler IO UnionQuery
271+ unionQuery = do
272+ returnUser <- randomIO
273+ if returnUser
274+ then pure (unionValue @User user)
275+ else pure (unionValue @Calculator calculator)
165276```
166277
167- The output object `Object'` has a `ToJSON` instance:
168-
169- `` `
170- λ map (\( Success o) -> Aeson.encode o) hello
171- "{\" me\" :\" hey ho to me\" }"
172- `` `
278+ The important thing here is that we have to wrap the actual objects we return
279+ using `unionValue`.
173280
281+ Note that while `unionValue` looks a bit like `unsafeCoerce` by forcing one
282+ type to become another type, it's actually type-safe because we use a
283+ *type-index* to pick the correct type from the union. Using e.g. `unionValue
284+ @HelloWorld handler` will not compile because `HelloWorld` is not in the
285+ union.
174286
175287## Where next?
176288
177289We have an
178290[examples](https://github.com/jml/graphql-api/tree/master/tests/Examples)
179291directory showing full code examples.
180292
293+ We also have a fair number of [end-to-end
294+ tests](https://github.com/jml/graphql-api/tree/master/tests/EndToEndTests.hs)
295+ based on an [example
296+ schema](https://github.com/jml/graphql-api/tree/master/tests/ExampleSchema.hs)
297+ that you might find interesting.
298+
181299If you want to try the examples in this tutorial you can run:
182300
183301```bash
0 commit comments