docs: Move link to the new "external tutorials" area.
[oota-llvm.git] / docs / tutorial / OCamlLangImpl3.rst
1 ========================================
2 Kaleidoscope: Code generation to LLVM IR
3 ========================================
4
5 .. contents::
6    :local:
7
8 Written by `Chris Lattner <mailto:sabre@nondot.org>`_ and `Erick
9 Tryzelaar <mailto:idadesub@users.sourceforge.net>`_
10
11 Chapter 3 Introduction
12 ======================
13
14 Welcome to Chapter 3 of the "`Implementing a language with
15 LLVM <index.html>`_" tutorial. This chapter shows you how to transform
16 the `Abstract Syntax Tree <OCamlLangImpl2.html>`_, built in Chapter 2,
17 into LLVM IR. This will teach you a little bit about how LLVM does
18 things, as well as demonstrate how easy it is to use. It's much more
19 work to build a lexer and parser than it is to generate LLVM IR code. :)
20
21 **Please note**: the code in this chapter and later require LLVM 2.3 or
22 LLVM SVN to work. LLVM 2.2 and before will not work with it.
23
24 Code Generation Setup
25 =====================
26
27 In order to generate LLVM IR, we want some simple setup to get started.
28 First we define virtual code generation (codegen) methods in each AST
29 class:
30
31 .. code-block:: ocaml
32
33     let rec codegen_expr = function
34       | Ast.Number n -> ...
35       | Ast.Variable name -> ...
36
37 The ``Codegen.codegen_expr`` function says to emit IR for that AST node
38 along with all the things it depends on, and they all return an LLVM
39 Value object. "Value" is the class used to represent a "`Static Single
40 Assignment
41 (SSA) <http://en.wikipedia.org/wiki/Static_single_assignment_form>`_
42 register" or "SSA value" in LLVM. The most distinct aspect of SSA values
43 is that their value is computed as the related instruction executes, and
44 it does not get a new value until (and if) the instruction re-executes.
45 In other words, there is no way to "change" an SSA value. For more
46 information, please read up on `Static Single
47 Assignment <http://en.wikipedia.org/wiki/Static_single_assignment_form>`_
48 - the concepts are really quite natural once you grok them.
49
50 The second thing we want is an "Error" exception like we used for the
51 parser, which will be used to report errors found during code generation
52 (for example, use of an undeclared parameter):
53
54 .. code-block:: ocaml
55
56     exception Error of string
57
58     let context = global_context ()
59     let the_module = create_module context "my cool jit"
60     let builder = builder context
61     let named_values:(string, llvalue) Hashtbl.t = Hashtbl.create 10
62     let double_type = double_type context
63
64 The static variables will be used during code generation.
65 ``Codgen.the_module`` is the LLVM construct that contains all of the
66 functions and global variables in a chunk of code. In many ways, it is
67 the top-level structure that the LLVM IR uses to contain code.
68
69 The ``Codegen.builder`` object is a helper object that makes it easy to
70 generate LLVM instructions. Instances of the
71 ```IRBuilder`` <http://llvm.org/doxygen/IRBuilder_8h-source.html>`_
72 class keep track of the current place to insert instructions and has
73 methods to create new instructions.
74
75 The ``Codegen.named_values`` map keeps track of which values are defined
76 in the current scope and what their LLVM representation is. (In other
77 words, it is a symbol table for the code). In this form of Kaleidoscope,
78 the only things that can be referenced are function parameters. As such,
79 function parameters will be in this map when generating code for their
80 function body.
81
82 With these basics in place, we can start talking about how to generate
83 code for each expression. Note that this assumes that the
84 ``Codgen.builder`` has been set up to generate code *into* something.
85 For now, we'll assume that this has already been done, and we'll just
86 use it to emit code.
87
88 Expression Code Generation
89 ==========================
90
91 Generating LLVM code for expression nodes is very straightforward: less
92 than 30 lines of commented code for all four of our expression nodes.
93 First we'll do numeric literals:
94
95 .. code-block:: ocaml
96
97       | Ast.Number n -> const_float double_type n
98
99 In the LLVM IR, numeric constants are represented with the
100 ``ConstantFP`` class, which holds the numeric value in an ``APFloat``
101 internally (``APFloat`` has the capability of holding floating point
102 constants of Arbitrary Precision). This code basically just creates
103 and returns a ``ConstantFP``. Note that in the LLVM IR that constants
104 are all uniqued together and shared. For this reason, the API uses "the
105 foo::get(..)" idiom instead of "new foo(..)" or "foo::Create(..)".
106
107 .. code-block:: ocaml
108
109       | Ast.Variable name ->
110           (try Hashtbl.find named_values name with
111             | Not_found -> raise (Error "unknown variable name"))
112
113 References to variables are also quite simple using LLVM. In the simple
114 version of Kaleidoscope, we assume that the variable has already been
115 emitted somewhere and its value is available. In practice, the only
116 values that can be in the ``Codegen.named_values`` map are function
117 arguments. This code simply checks to see that the specified name is in
118 the map (if not, an unknown variable is being referenced) and returns
119 the value for it. In future chapters, we'll add support for `loop
120 induction variables <LangImpl5.html#for>`_ in the symbol table, and for
121 `local variables <LangImpl7.html#localvars>`_.
122
123 .. code-block:: ocaml
124
125       | Ast.Binary (op, lhs, rhs) ->
126           let lhs_val = codegen_expr lhs in
127           let rhs_val = codegen_expr rhs in
128           begin
129             match op with
130             | '+' -> build_fadd lhs_val rhs_val "addtmp" builder
131             | '-' -> build_fsub lhs_val rhs_val "subtmp" builder
132             | '*' -> build_fmul lhs_val rhs_val "multmp" builder
133             | '<' ->
134                 (* Convert bool 0/1 to double 0.0 or 1.0 *)
135                 let i = build_fcmp Fcmp.Ult lhs_val rhs_val "cmptmp" builder in
136                 build_uitofp i double_type "booltmp" builder
137             | _ -> raise (Error "invalid binary operator")
138           end
139
140 Binary operators start to get more interesting. The basic idea here is
141 that we recursively emit code for the left-hand side of the expression,
142 then the right-hand side, then we compute the result of the binary
143 expression. In this code, we do a simple switch on the opcode to create
144 the right LLVM instruction.
145
146 In the example above, the LLVM builder class is starting to show its
147 value. IRBuilder knows where to insert the newly created instruction,
148 all you have to do is specify what instruction to create (e.g. with
149 ``Llvm.create_add``), which operands to use (``lhs`` and ``rhs`` here)
150 and optionally provide a name for the generated instruction.
151
152 One nice thing about LLVM is that the name is just a hint. For instance,
153 if the code above emits multiple "addtmp" variables, LLVM will
154 automatically provide each one with an increasing, unique numeric
155 suffix. Local value names for instructions are purely optional, but it
156 makes it much easier to read the IR dumps.
157
158 `LLVM instructions <../LangRef.html#instref>`_ are constrained by strict
159 rules: for example, the Left and Right operators of an `add
160 instruction <../LangRef.html#i_add>`_ must have the same type, and the
161 result type of the add must match the operand types. Because all values
162 in Kaleidoscope are doubles, this makes for very simple code for add,
163 sub and mul.
164
165 On the other hand, LLVM specifies that the `fcmp
166 instruction <../LangRef.html#i_fcmp>`_ always returns an 'i1' value (a
167 one bit integer). The problem with this is that Kaleidoscope wants the
168 value to be a 0.0 or 1.0 value. In order to get these semantics, we
169 combine the fcmp instruction with a `uitofp
170 instruction <../LangRef.html#i_uitofp>`_. This instruction converts its
171 input integer into a floating point value by treating the input as an
172 unsigned value. In contrast, if we used the `sitofp
173 instruction <../LangRef.html#i_sitofp>`_, the Kaleidoscope '<' operator
174 would return 0.0 and -1.0, depending on the input value.
175
176 .. code-block:: ocaml
177
178       | Ast.Call (callee, args) ->
179           (* Look up the name in the module table. *)
180           let callee =
181             match lookup_function callee the_module with
182             | Some callee -> callee
183             | None -> raise (Error "unknown function referenced")
184           in
185           let params = params callee in
186
187           (* If argument mismatch error. *)
188           if Array.length params == Array.length args then () else
189             raise (Error "incorrect # arguments passed");
190           let args = Array.map codegen_expr args in
191           build_call callee args "calltmp" builder
192
193 Code generation for function calls is quite straightforward with LLVM.
194 The code above initially does a function name lookup in the LLVM
195 Module's symbol table. Recall that the LLVM Module is the container that
196 holds all of the functions we are JIT'ing. By giving each function the
197 same name as what the user specifies, we can use the LLVM symbol table
198 to resolve function names for us.
199
200 Once we have the function to call, we recursively codegen each argument
201 that is to be passed in, and create an LLVM `call
202 instruction <../LangRef.html#i_call>`_. Note that LLVM uses the native C
203 calling conventions by default, allowing these calls to also call into
204 standard library functions like "sin" and "cos", with no additional
205 effort.
206
207 This wraps up our handling of the four basic expressions that we have so
208 far in Kaleidoscope. Feel free to go in and add some more. For example,
209 by browsing the `LLVM language reference <../LangRef.html>`_ you'll find
210 several other interesting instructions that are really easy to plug into
211 our basic framework.
212
213 Function Code Generation
214 ========================
215
216 Code generation for prototypes and functions must handle a number of
217 details, which make their code less beautiful than expression code
218 generation, but allows us to illustrate some important points. First,
219 lets talk about code generation for prototypes: they are used both for
220 function bodies and external function declarations. The code starts
221 with:
222
223 .. code-block:: ocaml
224
225     let codegen_proto = function
226       | Ast.Prototype (name, args) ->
227           (* Make the function type: double(double,double) etc. *)
228           let doubles = Array.make (Array.length args) double_type in
229           let ft = function_type double_type doubles in
230           let f =
231             match lookup_function name the_module with
232
233 This code packs a lot of power into a few lines. Note first that this
234 function returns a "Function\*" instead of a "Value\*" (although at the
235 moment they both are modeled by ``llvalue`` in ocaml). Because a
236 "prototype" really talks about the external interface for a function
237 (not the value computed by an expression), it makes sense for it to
238 return the LLVM Function it corresponds to when codegen'd.
239
240 The call to ``Llvm.function_type`` creates the ``Llvm.llvalue`` that
241 should be used for a given Prototype. Since all function arguments in
242 Kaleidoscope are of type double, the first line creates a vector of "N"
243 LLVM double types. It then uses the ``Llvm.function_type`` method to
244 create a function type that takes "N" doubles as arguments, returns one
245 double as a result, and that is not vararg (that uses the function
246 ``Llvm.var_arg_function_type``). Note that Types in LLVM are uniqued
247 just like ``Constant``'s are, so you don't "new" a type, you "get" it.
248
249 The final line above checks if the function has already been defined in
250 ``Codegen.the_module``. If not, we will create it.
251
252 .. code-block:: ocaml
253
254             | None -> declare_function name ft the_module
255
256 This indicates the type and name to use, as well as which module to
257 insert into. By default we assume a function has
258 ``Llvm.Linkage.ExternalLinkage``. "`external
259 linkage <LangRef.html#linkage>`_" means that the function may be defined
260 outside the current module and/or that it is callable by functions
261 outside the module. The "``name``" passed in is the name the user
262 specified: this name is registered in "``Codegen.the_module``"s symbol
263 table, which is used by the function call code above.
264
265 In Kaleidoscope, I choose to allow redefinitions of functions in two
266 cases: first, we want to allow 'extern'ing a function more than once, as
267 long as the prototypes for the externs match (since all arguments have
268 the same type, we just have to check that the number of arguments
269 match). Second, we want to allow 'extern'ing a function and then
270 defining a body for it. This is useful when defining mutually recursive
271 functions.
272
273 .. code-block:: ocaml
274
275             (* If 'f' conflicted, there was already something named 'name'. If it
276              * has a body, don't allow redefinition or reextern. *)
277             | Some f ->
278                 (* If 'f' already has a body, reject this. *)
279                 if Array.length (basic_blocks f) == 0 then () else
280                   raise (Error "redefinition of function");
281
282                 (* If 'f' took a different number of arguments, reject. *)
283                 if Array.length (params f) == Array.length args then () else
284                   raise (Error "redefinition of function with different # args");
285                 f
286           in
287
288 In order to verify the logic above, we first check to see if the
289 pre-existing function is "empty". In this case, empty means that it has
290 no basic blocks in it, which means it has no body. If it has no body, it
291 is a forward declaration. Since we don't allow anything after a full
292 definition of the function, the code rejects this case. If the previous
293 reference to a function was an 'extern', we simply verify that the
294 number of arguments for that definition and this one match up. If not,
295 we emit an error.
296
297 .. code-block:: ocaml
298
299           (* Set names for all arguments. *)
300           Array.iteri (fun i a ->
301             let n = args.(i) in
302             set_value_name n a;
303             Hashtbl.add named_values n a;
304           ) (params f);
305           f
306
307 The last bit of code for prototypes loops over all of the arguments in
308 the function, setting the name of the LLVM Argument objects to match,
309 and registering the arguments in the ``Codegen.named_values`` map for
310 future use by the ``Ast.Variable`` variant. Once this is set up, it
311 returns the Function object to the caller. Note that we don't check for
312 conflicting argument names here (e.g. "extern foo(a b a)"). Doing so
313 would be very straight-forward with the mechanics we have already used
314 above.
315
316 .. code-block:: ocaml
317
318     let codegen_func = function
319       | Ast.Function (proto, body) ->
320           Hashtbl.clear named_values;
321           let the_function = codegen_proto proto in
322
323 Code generation for function definitions starts out simply enough: we
324 just codegen the prototype (Proto) and verify that it is ok. We then
325 clear out the ``Codegen.named_values`` map to make sure that there isn't
326 anything in it from the last function we compiled. Code generation of
327 the prototype ensures that there is an LLVM Function object that is
328 ready to go for us.
329
330 .. code-block:: ocaml
331
332           (* Create a new basic block to start insertion into. *)
333           let bb = append_block context "entry" the_function in
334           position_at_end bb builder;
335
336           try
337             let ret_val = codegen_expr body in
338
339 Now we get to the point where the ``Codegen.builder`` is set up. The
340 first line creates a new `basic
341 block <http://en.wikipedia.org/wiki/Basic_block>`_ (named "entry"),
342 which is inserted into ``the_function``. The second line then tells the
343 builder that new instructions should be inserted into the end of the new
344 basic block. Basic blocks in LLVM are an important part of functions
345 that define the `Control Flow
346 Graph <http://en.wikipedia.org/wiki/Control_flow_graph>`_. Since we
347 don't have any control flow, our functions will only contain one block
348 at this point. We'll fix this in `Chapter 5 <OCamlLangImpl5.html>`_ :).
349
350 .. code-block:: ocaml
351
352             let ret_val = codegen_expr body in
353
354             (* Finish off the function. *)
355             let _ = build_ret ret_val builder in
356
357             (* Validate the generated code, checking for consistency. *)
358             Llvm_analysis.assert_valid_function the_function;
359
360             the_function
361
362 Once the insertion point is set up, we call the ``Codegen.codegen_func``
363 method for the root expression of the function. If no error happens,
364 this emits code to compute the expression into the entry block and
365 returns the value that was computed. Assuming no error, we then create
366 an LLVM `ret instruction <../LangRef.html#i_ret>`_, which completes the
367 function. Once the function is built, we call
368 ``Llvm_analysis.assert_valid_function``, which is provided by LLVM. This
369 function does a variety of consistency checks on the generated code, to
370 determine if our compiler is doing everything right. Using this is
371 important: it can catch a lot of bugs. Once the function is finished and
372 validated, we return it.
373
374 .. code-block:: ocaml
375
376           with e ->
377             delete_function the_function;
378             raise e
379
380 The only piece left here is handling of the error case. For simplicity,
381 we handle this by merely deleting the function we produced with the
382 ``Llvm.delete_function`` method. This allows the user to redefine a
383 function that they incorrectly typed in before: if we didn't delete it,
384 it would live in the symbol table, with a body, preventing future
385 redefinition.
386
387 This code does have a bug, though. Since the ``Codegen.codegen_proto``
388 can return a previously defined forward declaration, our code can
389 actually delete a forward declaration. There are a number of ways to fix
390 this bug, see what you can come up with! Here is a testcase:
391
392 ::
393
394     extern foo(a b);     # ok, defines foo.
395     def foo(a b) c;      # error, 'c' is invalid.
396     def bar() foo(1, 2); # error, unknown function "foo"
397
398 Driver Changes and Closing Thoughts
399 ===================================
400
401 For now, code generation to LLVM doesn't really get us much, except that
402 we can look at the pretty IR calls. The sample code inserts calls to
403 Codegen into the "``Toplevel.main_loop``", and then dumps out the LLVM
404 IR. This gives a nice way to look at the LLVM IR for simple functions.
405 For example:
406
407 ::
408
409     ready> 4+5;
410     Read top-level expression:
411     define double @""() {
412     entry:
413             %addtmp = fadd double 4.000000e+00, 5.000000e+00
414             ret double %addtmp
415     }
416
417 Note how the parser turns the top-level expression into anonymous
418 functions for us. This will be handy when we add `JIT
419 support <OCamlLangImpl4.html#jit>`_ in the next chapter. Also note that
420 the code is very literally transcribed, no optimizations are being
421 performed. We will `add
422 optimizations <OCamlLangImpl4.html#trivialconstfold>`_ explicitly in the
423 next chapter.
424
425 ::
426
427     ready> def foo(a b) a*a + 2*a*b + b*b;
428     Read function definition:
429     define double @foo(double %a, double %b) {
430     entry:
431             %multmp = fmul double %a, %a
432             %multmp1 = fmul double 2.000000e+00, %a
433             %multmp2 = fmul double %multmp1, %b
434             %addtmp = fadd double %multmp, %multmp2
435             %multmp3 = fmul double %b, %b
436             %addtmp4 = fadd double %addtmp, %multmp3
437             ret double %addtmp4
438     }
439
440 This shows some simple arithmetic. Notice the striking similarity to the
441 LLVM builder calls that we use to create the instructions.
442
443 ::
444
445     ready> def bar(a) foo(a, 4.0) + bar(31337);
446     Read function definition:
447     define double @bar(double %a) {
448     entry:
449             %calltmp = call double @foo(double %a, double 4.000000e+00)
450             %calltmp1 = call double @bar(double 3.133700e+04)
451             %addtmp = fadd double %calltmp, %calltmp1
452             ret double %addtmp
453     }
454
455 This shows some function calls. Note that this function will take a long
456 time to execute if you call it. In the future we'll add conditional
457 control flow to actually make recursion useful :).
458
459 ::
460
461     ready> extern cos(x);
462     Read extern:
463     declare double @cos(double)
464
465     ready> cos(1.234);
466     Read top-level expression:
467     define double @""() {
468     entry:
469             %calltmp = call double @cos(double 1.234000e+00)
470             ret double %calltmp
471     }
472
473 This shows an extern for the libm "cos" function, and a call to it.
474
475 ::
476
477     ready> ^D
478     ; ModuleID = 'my cool jit'
479
480     define double @""() {
481     entry:
482             %addtmp = fadd double 4.000000e+00, 5.000000e+00
483             ret double %addtmp
484     }
485
486     define double @foo(double %a, double %b) {
487     entry:
488             %multmp = fmul double %a, %a
489             %multmp1 = fmul double 2.000000e+00, %a
490             %multmp2 = fmul double %multmp1, %b
491             %addtmp = fadd double %multmp, %multmp2
492             %multmp3 = fmul double %b, %b
493             %addtmp4 = fadd double %addtmp, %multmp3
494             ret double %addtmp4
495     }
496
497     define double @bar(double %a) {
498     entry:
499             %calltmp = call double @foo(double %a, double 4.000000e+00)
500             %calltmp1 = call double @bar(double 3.133700e+04)
501             %addtmp = fadd double %calltmp, %calltmp1
502             ret double %addtmp
503     }
504
505     declare double @cos(double)
506
507     define double @""() {
508     entry:
509             %calltmp = call double @cos(double 1.234000e+00)
510             ret double %calltmp
511     }
512
513 When you quit the current demo, it dumps out the IR for the entire
514 module generated. Here you can see the big picture with all the
515 functions referencing each other.
516
517 This wraps up the third chapter of the Kaleidoscope tutorial. Up next,
518 we'll describe how to `add JIT codegen and optimizer
519 support <OCamlLangImpl4.html>`_ to this so we can actually start running
520 code!
521
522 Full Code Listing
523 =================
524
525 Here is the complete code listing for our running example, enhanced with
526 the LLVM code generator. Because this uses the LLVM libraries, we need
527 to link them in. To do this, we use the
528 `llvm-config <http://llvm.org/cmds/llvm-config.html>`_ tool to inform
529 our makefile/command line about which options to use:
530
531 .. code-block:: bash
532
533     # Compile
534     ocamlbuild toy.byte
535     # Run
536     ./toy.byte
537
538 Here is the code:
539
540 \_tags:
541     ::
542
543         <{lexer,parser}.ml>: use_camlp4, pp(camlp4of)
544         <*.{byte,native}>: g++, use_llvm, use_llvm_analysis
545
546 myocamlbuild.ml:
547     .. code-block:: ocaml
548
549         open Ocamlbuild_plugin;;
550
551         ocaml_lib ~extern:true "llvm";;
552         ocaml_lib ~extern:true "llvm_analysis";;
553
554         flag ["link"; "ocaml"; "g++"] (S[A"-cc"; A"g++"]);;
555
556 token.ml:
557     .. code-block:: ocaml
558
559         (*===----------------------------------------------------------------------===
560          * Lexer Tokens
561          *===----------------------------------------------------------------------===*)
562
563         (* The lexer returns these 'Kwd' if it is an unknown character, otherwise one of
564          * these others for known things. *)
565         type token =
566           (* commands *)
567           | Def | Extern
568
569           (* primary *)
570           | Ident of string | Number of float
571
572           (* unknown *)
573           | Kwd of char
574
575 lexer.ml:
576     .. code-block:: ocaml
577
578         (*===----------------------------------------------------------------------===
579          * Lexer
580          *===----------------------------------------------------------------------===*)
581
582         let rec lex = parser
583           (* Skip any whitespace. *)
584           | [< ' (' ' | '\n' | '\r' | '\t'); stream >] -> lex stream
585
586           (* identifier: [a-zA-Z][a-zA-Z0-9] *)
587           | [< ' ('A' .. 'Z' | 'a' .. 'z' as c); stream >] ->
588               let buffer = Buffer.create 1 in
589               Buffer.add_char buffer c;
590               lex_ident buffer stream
591
592           (* number: [0-9.]+ *)
593           | [< ' ('0' .. '9' as c); stream >] ->
594               let buffer = Buffer.create 1 in
595               Buffer.add_char buffer c;
596               lex_number buffer stream
597
598           (* Comment until end of line. *)
599           | [< ' ('#'); stream >] ->
600               lex_comment stream
601
602           (* Otherwise, just return the character as its ascii value. *)
603           | [< 'c; stream >] ->
604               [< 'Token.Kwd c; lex stream >]
605
606           (* end of stream. *)
607           | [< >] -> [< >]
608
609         and lex_number buffer = parser
610           | [< ' ('0' .. '9' | '.' as c); stream >] ->
611               Buffer.add_char buffer c;
612               lex_number buffer stream
613           | [< stream=lex >] ->
614               [< 'Token.Number (float_of_string (Buffer.contents buffer)); stream >]
615
616         and lex_ident buffer = parser
617           | [< ' ('A' .. 'Z' | 'a' .. 'z' | '0' .. '9' as c); stream >] ->
618               Buffer.add_char buffer c;
619               lex_ident buffer stream
620           | [< stream=lex >] ->
621               match Buffer.contents buffer with
622               | "def" -> [< 'Token.Def; stream >]
623               | "extern" -> [< 'Token.Extern; stream >]
624               | id -> [< 'Token.Ident id; stream >]
625
626         and lex_comment = parser
627           | [< ' ('\n'); stream=lex >] -> stream
628           | [< 'c; e=lex_comment >] -> e
629           | [< >] -> [< >]
630
631 ast.ml:
632     .. code-block:: ocaml
633
634         (*===----------------------------------------------------------------------===
635          * Abstract Syntax Tree (aka Parse Tree)
636          *===----------------------------------------------------------------------===*)
637
638         (* expr - Base type for all expression nodes. *)
639         type expr =
640           (* variant for numeric literals like "1.0". *)
641           | Number of float
642
643           (* variant for referencing a variable, like "a". *)
644           | Variable of string
645
646           (* variant for a binary operator. *)
647           | Binary of char * expr * expr
648
649           (* variant for function calls. *)
650           | Call of string * expr array
651
652         (* proto - This type represents the "prototype" for a function, which captures
653          * its name, and its argument names (thus implicitly the number of arguments the
654          * function takes). *)
655         type proto = Prototype of string * string array
656
657         (* func - This type represents a function definition itself. *)
658         type func = Function of proto * expr
659
660 parser.ml:
661     .. code-block:: ocaml
662
663         (*===---------------------------------------------------------------------===
664          * Parser
665          *===---------------------------------------------------------------------===*)
666
667         (* binop_precedence - This holds the precedence for each binary operator that is
668          * defined *)
669         let binop_precedence:(char, int) Hashtbl.t = Hashtbl.create 10
670
671         (* precedence - Get the precedence of the pending binary operator token. *)
672         let precedence c = try Hashtbl.find binop_precedence c with Not_found -> -1
673
674         (* primary
675          *   ::= identifier
676          *   ::= numberexpr
677          *   ::= parenexpr *)
678         let rec parse_primary = parser
679           (* numberexpr ::= number *)
680           | [< 'Token.Number n >] -> Ast.Number n
681
682           (* parenexpr ::= '(' expression ')' *)
683           | [< 'Token.Kwd '('; e=parse_expr; 'Token.Kwd ')' ?? "expected ')'" >] -> e
684
685           (* identifierexpr
686            *   ::= identifier
687            *   ::= identifier '(' argumentexpr ')' *)
688           | [< 'Token.Ident id; stream >] ->
689               let rec parse_args accumulator = parser
690                 | [< e=parse_expr; stream >] ->
691                     begin parser
692                       | [< 'Token.Kwd ','; e=parse_args (e :: accumulator) >] -> e
693                       | [< >] -> e :: accumulator
694                     end stream
695                 | [< >] -> accumulator
696               in
697               let rec parse_ident id = parser
698                 (* Call. *)
699                 | [< 'Token.Kwd '(';
700                      args=parse_args [];
701                      'Token.Kwd ')' ?? "expected ')'">] ->
702                     Ast.Call (id, Array.of_list (List.rev args))
703
704                 (* Simple variable ref. *)
705                 | [< >] -> Ast.Variable id
706               in
707               parse_ident id stream
708
709           | [< >] -> raise (Stream.Error "unknown token when expecting an expression.")
710
711         (* binoprhs
712          *   ::= ('+' primary)* *)
713         and parse_bin_rhs expr_prec lhs stream =
714           match Stream.peek stream with
715           (* If this is a binop, find its precedence. *)
716           | Some (Token.Kwd c) when Hashtbl.mem binop_precedence c ->
717               let token_prec = precedence c in
718
719               (* If this is a binop that binds at least as tightly as the current binop,
720                * consume it, otherwise we are done. *)
721               if token_prec < expr_prec then lhs else begin
722                 (* Eat the binop. *)
723                 Stream.junk stream;
724
725                 (* Parse the primary expression after the binary operator. *)
726                 let rhs = parse_primary stream in
727
728                 (* Okay, we know this is a binop. *)
729                 let rhs =
730                   match Stream.peek stream with
731                   | Some (Token.Kwd c2) ->
732                       (* If BinOp binds less tightly with rhs than the operator after
733                        * rhs, let the pending operator take rhs as its lhs. *)
734                       let next_prec = precedence c2 in
735                       if token_prec < next_prec
736                       then parse_bin_rhs (token_prec + 1) rhs stream
737                       else rhs
738                   | _ -> rhs
739                 in
740
741                 (* Merge lhs/rhs. *)
742                 let lhs = Ast.Binary (c, lhs, rhs) in
743                 parse_bin_rhs expr_prec lhs stream
744               end
745           | _ -> lhs
746
747         (* expression
748          *   ::= primary binoprhs *)
749         and parse_expr = parser
750           | [< lhs=parse_primary; stream >] -> parse_bin_rhs 0 lhs stream
751
752         (* prototype
753          *   ::= id '(' id* ')' *)
754         let parse_prototype =
755           let rec parse_args accumulator = parser
756             | [< 'Token.Ident id; e=parse_args (id::accumulator) >] -> e
757             | [< >] -> accumulator
758           in
759
760           parser
761           | [< 'Token.Ident id;
762                'Token.Kwd '(' ?? "expected '(' in prototype";
763                args=parse_args [];
764                'Token.Kwd ')' ?? "expected ')' in prototype" >] ->
765               (* success. *)
766               Ast.Prototype (id, Array.of_list (List.rev args))
767
768           | [< >] ->
769               raise (Stream.Error "expected function name in prototype")
770
771         (* definition ::= 'def' prototype expression *)
772         let parse_definition = parser
773           | [< 'Token.Def; p=parse_prototype; e=parse_expr >] ->
774               Ast.Function (p, e)
775
776         (* toplevelexpr ::= expression *)
777         let parse_toplevel = parser
778           | [< e=parse_expr >] ->
779               (* Make an anonymous proto. *)
780               Ast.Function (Ast.Prototype ("", [||]), e)
781
782         (*  external ::= 'extern' prototype *)
783         let parse_extern = parser
784           | [< 'Token.Extern; e=parse_prototype >] -> e
785
786 codegen.ml:
787     .. code-block:: ocaml
788
789         (*===----------------------------------------------------------------------===
790          * Code Generation
791          *===----------------------------------------------------------------------===*)
792
793         open Llvm
794
795         exception Error of string
796
797         let context = global_context ()
798         let the_module = create_module context "my cool jit"
799         let builder = builder context
800         let named_values:(string, llvalue) Hashtbl.t = Hashtbl.create 10
801         let double_type = double_type context
802
803         let rec codegen_expr = function
804           | Ast.Number n -> const_float double_type n
805           | Ast.Variable name ->
806               (try Hashtbl.find named_values name with
807                 | Not_found -> raise (Error "unknown variable name"))
808           | Ast.Binary (op, lhs, rhs) ->
809               let lhs_val = codegen_expr lhs in
810               let rhs_val = codegen_expr rhs in
811               begin
812                 match op with
813                 | '+' -> build_add lhs_val rhs_val "addtmp" builder
814                 | '-' -> build_sub lhs_val rhs_val "subtmp" builder
815                 | '*' -> build_mul lhs_val rhs_val "multmp" builder
816                 | '<' ->
817                     (* Convert bool 0/1 to double 0.0 or 1.0 *)
818                     let i = build_fcmp Fcmp.Ult lhs_val rhs_val "cmptmp" builder in
819                     build_uitofp i double_type "booltmp" builder
820                 | _ -> raise (Error "invalid binary operator")
821               end
822           | Ast.Call (callee, args) ->
823               (* Look up the name in the module table. *)
824               let callee =
825                 match lookup_function callee the_module with
826                 | Some callee -> callee
827                 | None -> raise (Error "unknown function referenced")
828               in
829               let params = params callee in
830
831               (* If argument mismatch error. *)
832               if Array.length params == Array.length args then () else
833                 raise (Error "incorrect # arguments passed");
834               let args = Array.map codegen_expr args in
835               build_call callee args "calltmp" builder
836
837         let codegen_proto = function
838           | Ast.Prototype (name, args) ->
839               (* Make the function type: double(double,double) etc. *)
840               let doubles = Array.make (Array.length args) double_type in
841               let ft = function_type double_type doubles in
842               let f =
843                 match lookup_function name the_module with
844                 | None -> declare_function name ft the_module
845
846                 (* If 'f' conflicted, there was already something named 'name'. If it
847                  * has a body, don't allow redefinition or reextern. *)
848                 | Some f ->
849                     (* If 'f' already has a body, reject this. *)
850                     if block_begin f <> At_end f then
851                       raise (Error "redefinition of function");
852
853                     (* If 'f' took a different number of arguments, reject. *)
854                     if element_type (type_of f) <> ft then
855                       raise (Error "redefinition of function with different # args");
856                     f
857               in
858
859               (* Set names for all arguments. *)
860               Array.iteri (fun i a ->
861                 let n = args.(i) in
862                 set_value_name n a;
863                 Hashtbl.add named_values n a;
864               ) (params f);
865               f
866
867         let codegen_func = function
868           | Ast.Function (proto, body) ->
869               Hashtbl.clear named_values;
870               let the_function = codegen_proto proto in
871
872               (* Create a new basic block to start insertion into. *)
873               let bb = append_block context "entry" the_function in
874               position_at_end bb builder;
875
876               try
877                 let ret_val = codegen_expr body in
878
879                 (* Finish off the function. *)
880                 let _ = build_ret ret_val builder in
881
882                 (* Validate the generated code, checking for consistency. *)
883                 Llvm_analysis.assert_valid_function the_function;
884
885                 the_function
886               with e ->
887                 delete_function the_function;
888                 raise e
889
890 toplevel.ml:
891     .. code-block:: ocaml
892
893         (*===----------------------------------------------------------------------===
894          * Top-Level parsing and JIT Driver
895          *===----------------------------------------------------------------------===*)
896
897         open Llvm
898
899         (* top ::= definition | external | expression | ';' *)
900         let rec main_loop stream =
901           match Stream.peek stream with
902           | None -> ()
903
904           (* ignore top-level semicolons. *)
905           | Some (Token.Kwd ';') ->
906               Stream.junk stream;
907               main_loop stream
908
909           | Some token ->
910               begin
911                 try match token with
912                 | Token.Def ->
913                     let e = Parser.parse_definition stream in
914                     print_endline "parsed a function definition.";
915                     dump_value (Codegen.codegen_func e);
916                 | Token.Extern ->
917                     let e = Parser.parse_extern stream in
918                     print_endline "parsed an extern.";
919                     dump_value (Codegen.codegen_proto e);
920                 | _ ->
921                     (* Evaluate a top-level expression into an anonymous function. *)
922                     let e = Parser.parse_toplevel stream in
923                     print_endline "parsed a top-level expr";
924                     dump_value (Codegen.codegen_func e);
925                 with Stream.Error s | Codegen.Error s ->
926                   (* Skip token for error recovery. *)
927                   Stream.junk stream;
928                   print_endline s;
929               end;
930               print_string "ready> "; flush stdout;
931               main_loop stream
932
933 toy.ml:
934     .. code-block:: ocaml
935
936         (*===----------------------------------------------------------------------===
937          * Main driver code.
938          *===----------------------------------------------------------------------===*)
939
940         open Llvm
941
942         let main () =
943           (* Install standard binary operators.
944            * 1 is the lowest precedence. *)
945           Hashtbl.add Parser.binop_precedence '<' 10;
946           Hashtbl.add Parser.binop_precedence '+' 20;
947           Hashtbl.add Parser.binop_precedence '-' 20;
948           Hashtbl.add Parser.binop_precedence '*' 40;    (* highest. *)
949
950           (* Prime the first token. *)
951           print_string "ready> "; flush stdout;
952           let stream = Lexer.lex (Stream.of_channel stdin) in
953
954           (* Run the main "interpreter loop" now. *)
955           Toplevel.main_loop stream;
956
957           (* Print out all the generated code. *)
958           dump_module Codegen.the_module
959         ;;
960
961         main ()
962
963 `Next: Adding JIT and Optimizer Support <OCamlLangImpl4.html>`_
964