OCamlLangImpl5.rst 51 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350
  1. ==================================================
  2. Kaleidoscope: Extending the Language: Control Flow
  3. ==================================================
  4. .. contents::
  5. :local:
  6. Chapter 5 Introduction
  7. ======================
  8. Welcome to Chapter 5 of the "`Implementing a language with
  9. LLVM <index.html>`_" tutorial. Parts 1-4 described the implementation of
  10. the simple Kaleidoscope language and included support for generating
  11. LLVM IR, followed by optimizations and a JIT compiler. Unfortunately, as
  12. presented, Kaleidoscope is mostly useless: it has no control flow other
  13. than call and return. This means that you can't have conditional
  14. branches in the code, significantly limiting its power. In this episode
  15. of "build that compiler", we'll extend Kaleidoscope to have an
  16. if/then/else expression plus a simple 'for' loop.
  17. If/Then/Else
  18. ============
  19. Extending Kaleidoscope to support if/then/else is quite straightforward.
  20. It basically requires adding lexer support for this "new" concept to the
  21. lexer, parser, AST, and LLVM code emitter. This example is nice, because
  22. it shows how easy it is to "grow" a language over time, incrementally
  23. extending it as new ideas are discovered.
  24. Before we get going on "how" we add this extension, lets talk about
  25. "what" we want. The basic idea is that we want to be able to write this
  26. sort of thing:
  27. ::
  28. def fib(x)
  29. if x < 3 then
  30. 1
  31. else
  32. fib(x-1)+fib(x-2);
  33. In Kaleidoscope, every construct is an expression: there are no
  34. statements. As such, the if/then/else expression needs to return a value
  35. like any other. Since we're using a mostly functional form, we'll have
  36. it evaluate its conditional, then return the 'then' or 'else' value
  37. based on how the condition was resolved. This is very similar to the C
  38. "?:" expression.
  39. The semantics of the if/then/else expression is that it evaluates the
  40. condition to a boolean equality value: 0.0 is considered to be false and
  41. everything else is considered to be true. If the condition is true, the
  42. first subexpression is evaluated and returned, if the condition is
  43. false, the second subexpression is evaluated and returned. Since
  44. Kaleidoscope allows side-effects, this behavior is important to nail
  45. down.
  46. Now that we know what we "want", lets break this down into its
  47. constituent pieces.
  48. Lexer Extensions for If/Then/Else
  49. ---------------------------------
  50. The lexer extensions are straightforward. First we add new variants for
  51. the relevant tokens:
  52. .. code-block:: ocaml
  53. (* control *)
  54. | If | Then | Else | For | In
  55. Once we have that, we recognize the new keywords in the lexer. This is
  56. pretty simple stuff:
  57. .. code-block:: ocaml
  58. ...
  59. match Buffer.contents buffer with
  60. | "def" -> [< 'Token.Def; stream >]
  61. | "extern" -> [< 'Token.Extern; stream >]
  62. | "if" -> [< 'Token.If; stream >]
  63. | "then" -> [< 'Token.Then; stream >]
  64. | "else" -> [< 'Token.Else; stream >]
  65. | "for" -> [< 'Token.For; stream >]
  66. | "in" -> [< 'Token.In; stream >]
  67. | id -> [< 'Token.Ident id; stream >]
  68. AST Extensions for If/Then/Else
  69. -------------------------------
  70. To represent the new expression we add a new AST variant for it:
  71. .. code-block:: ocaml
  72. type expr =
  73. ...
  74. (* variant for if/then/else. *)
  75. | If of expr * expr * expr
  76. The AST variant just has pointers to the various subexpressions.
  77. Parser Extensions for If/Then/Else
  78. ----------------------------------
  79. Now that we have the relevant tokens coming from the lexer and we have
  80. the AST node to build, our parsing logic is relatively straightforward.
  81. Next we add a new case for parsing a if-expression as a primary expression:
  82. .. code-block:: ocaml
  83. let rec parse_primary = parser
  84. ...
  85. (* ifexpr ::= 'if' expr 'then' expr 'else' expr *)
  86. | [< 'Token.If; c=parse_expr;
  87. 'Token.Then ?? "expected 'then'"; t=parse_expr;
  88. 'Token.Else ?? "expected 'else'"; e=parse_expr >] ->
  89. Ast.If (c, t, e)
  90. LLVM IR for If/Then/Else
  91. ------------------------
  92. Now that we have it parsing and building the AST, the final piece is
  93. adding LLVM code generation support. This is the most interesting part
  94. of the if/then/else example, because this is where it starts to
  95. introduce new concepts. All of the code above has been thoroughly
  96. described in previous chapters.
  97. To motivate the code we want to produce, lets take a look at a simple
  98. example. Consider:
  99. ::
  100. extern foo();
  101. extern bar();
  102. def baz(x) if x then foo() else bar();
  103. If you disable optimizations, the code you'll (soon) get from
  104. Kaleidoscope looks like this:
  105. .. code-block:: llvm
  106. declare double @foo()
  107. declare double @bar()
  108. define double @baz(double %x) {
  109. entry:
  110. %ifcond = fcmp one double %x, 0.000000e+00
  111. br i1 %ifcond, label %then, label %else
  112. then: ; preds = %entry
  113. %calltmp = call double @foo()
  114. br label %ifcont
  115. else: ; preds = %entry
  116. %calltmp1 = call double @bar()
  117. br label %ifcont
  118. ifcont: ; preds = %else, %then
  119. %iftmp = phi double [ %calltmp, %then ], [ %calltmp1, %else ]
  120. ret double %iftmp
  121. }
  122. To visualize the control flow graph, you can use a nifty feature of the
  123. LLVM '`opt <http://llvm.org/cmds/opt.html>`_' tool. If you put this LLVM
  124. IR into "t.ll" and run "``llvm-as < t.ll | opt -analyze -view-cfg``", `a
  125. window will pop up <../ProgrammersManual.html#viewing-graphs-while-debugging-code>`_ and you'll
  126. see this graph:
  127. .. figure:: MyFirstLanguageFrontend/LangImpl05-cfg.png
  128. :align: center
  129. :alt: Example CFG
  130. Example CFG
  131. Another way to get this is to call
  132. "``Llvm_analysis.view_function_cfg f``" or
  133. "``Llvm_analysis.view_function_cfg_only f``" (where ``f`` is a
  134. "``Function``") either by inserting actual calls into the code and
  135. recompiling or by calling these in the debugger. LLVM has many nice
  136. features for visualizing various graphs.
  137. Getting back to the generated code, it is fairly simple: the entry block
  138. evaluates the conditional expression ("x" in our case here) and compares
  139. the result to 0.0 with the "``fcmp one``" instruction ('one' is "Ordered
  140. and Not Equal"). Based on the result of this expression, the code jumps
  141. to either the "then" or "else" blocks, which contain the expressions for
  142. the true/false cases.
  143. Once the then/else blocks are finished executing, they both branch back
  144. to the 'ifcont' block to execute the code that happens after the
  145. if/then/else. In this case the only thing left to do is to return to the
  146. caller of the function. The question then becomes: how does the code
  147. know which expression to return?
  148. The answer to this question involves an important SSA operation: the
  149. `Phi
  150. operation <http://en.wikipedia.org/wiki/Static_single_assignment_form>`_.
  151. If you're not familiar with SSA, `the wikipedia
  152. article <http://en.wikipedia.org/wiki/Static_single_assignment_form>`_
  153. is a good introduction and there are various other introductions to it
  154. available on your favorite search engine. The short version is that
  155. "execution" of the Phi operation requires "remembering" which block
  156. control came from. The Phi operation takes on the value corresponding to
  157. the input control block. In this case, if control comes in from the
  158. "then" block, it gets the value of "calltmp". If control comes from the
  159. "else" block, it gets the value of "calltmp1".
  160. At this point, you are probably starting to think "Oh no! This means my
  161. simple and elegant front-end will have to start generating SSA form in
  162. order to use LLVM!". Fortunately, this is not the case, and we strongly
  163. advise *not* implementing an SSA construction algorithm in your
  164. front-end unless there is an amazingly good reason to do so. In
  165. practice, there are two sorts of values that float around in code
  166. written for your average imperative programming language that might need
  167. Phi nodes:
  168. #. Code that involves user variables: ``x = 1; x = x + 1;``
  169. #. Values that are implicit in the structure of your AST, such as the
  170. Phi node in this case.
  171. In `Chapter 7 <OCamlLangImpl7.html>`_ of this tutorial ("mutable
  172. variables"), we'll talk about #1 in depth. For now, just believe me that
  173. you don't need SSA construction to handle this case. For #2, you have
  174. the choice of using the techniques that we will describe for #1, or you
  175. can insert Phi nodes directly, if convenient. In this case, it is really
  176. really easy to generate the Phi node, so we choose to do it directly.
  177. Okay, enough of the motivation and overview, lets generate code!
  178. Code Generation for If/Then/Else
  179. --------------------------------
  180. In order to generate code for this, we implement the ``Codegen`` method
  181. for ``IfExprAST``:
  182. .. code-block:: ocaml
  183. let rec codegen_expr = function
  184. ...
  185. | Ast.If (cond, then_, else_) ->
  186. let cond = codegen_expr cond in
  187. (* Convert condition to a bool by comparing equal to 0.0 *)
  188. let zero = const_float double_type 0.0 in
  189. let cond_val = build_fcmp Fcmp.One cond zero "ifcond" builder in
  190. This code is straightforward and similar to what we saw before. We emit
  191. the expression for the condition, then compare that value to zero to get
  192. a truth value as a 1-bit (bool) value.
  193. .. code-block:: ocaml
  194. (* Grab the first block so that we might later add the conditional branch
  195. * to it at the end of the function. *)
  196. let start_bb = insertion_block builder in
  197. let the_function = block_parent start_bb in
  198. let then_bb = append_block context "then" the_function in
  199. position_at_end then_bb builder;
  200. As opposed to the `C++ tutorial <LangImpl05.html>`_, we have to build our
  201. basic blocks bottom up since we can't have dangling BasicBlocks. We
  202. start off by saving a pointer to the first block (which might not be the
  203. entry block), which we'll need to build a conditional branch later. We
  204. do this by asking the ``builder`` for the current BasicBlock. The fourth
  205. line gets the current Function object that is being built. It gets this
  206. by the ``start_bb`` for its "parent" (the function it is currently
  207. embedded into).
  208. Once it has that, it creates one block. It is automatically appended
  209. into the function's list of blocks.
  210. .. code-block:: ocaml
  211. (* Emit 'then' value. *)
  212. position_at_end then_bb builder;
  213. let then_val = codegen_expr then_ in
  214. (* Codegen of 'then' can change the current block, update then_bb for the
  215. * phi. We create a new name because one is used for the phi node, and the
  216. * other is used for the conditional branch. *)
  217. let new_then_bb = insertion_block builder in
  218. We move the builder to start inserting into the "then" block. Strictly
  219. speaking, this call moves the insertion point to be at the end of the
  220. specified block. However, since the "then" block is empty, it also
  221. starts out by inserting at the beginning of the block. :)
  222. Once the insertion point is set, we recursively codegen the "then"
  223. expression from the AST.
  224. The final line here is quite subtle, but is very important. The basic
  225. issue is that when we create the Phi node in the merge block, we need to
  226. set up the block/value pairs that indicate how the Phi will work.
  227. Importantly, the Phi node expects to have an entry for each predecessor
  228. of the block in the CFG. Why then, are we getting the current block when
  229. we just set it to ThenBB 5 lines above? The problem is that the "Then"
  230. expression may actually itself change the block that the Builder is
  231. emitting into if, for example, it contains a nested "if/then/else"
  232. expression. Because calling Codegen recursively could arbitrarily change
  233. the notion of the current block, we are required to get an up-to-date
  234. value for code that will set up the Phi node.
  235. .. code-block:: ocaml
  236. (* Emit 'else' value. *)
  237. let else_bb = append_block context "else" the_function in
  238. position_at_end else_bb builder;
  239. let else_val = codegen_expr else_ in
  240. (* Codegen of 'else' can change the current block, update else_bb for the
  241. * phi. *)
  242. let new_else_bb = insertion_block builder in
  243. Code generation for the 'else' block is basically identical to codegen
  244. for the 'then' block.
  245. .. code-block:: ocaml
  246. (* Emit merge block. *)
  247. let merge_bb = append_block context "ifcont" the_function in
  248. position_at_end merge_bb builder;
  249. let incoming = [(then_val, new_then_bb); (else_val, new_else_bb)] in
  250. let phi = build_phi incoming "iftmp" builder in
  251. The first two lines here are now familiar: the first adds the "merge"
  252. block to the Function object. The second changes the insertion
  253. point so that newly created code will go into the "merge" block. Once
  254. that is done, we need to create the PHI node and set up the block/value
  255. pairs for the PHI.
  256. .. code-block:: ocaml
  257. (* Return to the start block to add the conditional branch. *)
  258. position_at_end start_bb builder;
  259. ignore (build_cond_br cond_val then_bb else_bb builder);
  260. Once the blocks are created, we can emit the conditional branch that
  261. chooses between them. Note that creating new blocks does not implicitly
  262. affect the IRBuilder, so it is still inserting into the block that the
  263. condition went into. This is why we needed to save the "start" block.
  264. .. code-block:: ocaml
  265. (* Set a unconditional branch at the end of the 'then' block and the
  266. * 'else' block to the 'merge' block. *)
  267. position_at_end new_then_bb builder; ignore (build_br merge_bb builder);
  268. position_at_end new_else_bb builder; ignore (build_br merge_bb builder);
  269. (* Finally, set the builder to the end of the merge block. *)
  270. position_at_end merge_bb builder;
  271. phi
  272. To finish off the blocks, we create an unconditional branch to the merge
  273. block. One interesting (and very important) aspect of the LLVM IR is
  274. that it `requires all basic blocks to be
  275. "terminated" <../LangRef.html#functionstructure>`_ with a `control flow
  276. instruction <../LangRef.html#terminators>`_ such as return or branch.
  277. This means that all control flow, *including fall throughs* must be made
  278. explicit in the LLVM IR. If you violate this rule, the verifier will
  279. emit an error.
  280. Finally, the CodeGen function returns the phi node as the value computed
  281. by the if/then/else expression. In our example above, this returned
  282. value will feed into the code for the top-level function, which will
  283. create the return instruction.
  284. Overall, we now have the ability to execute conditional code in
  285. Kaleidoscope. With this extension, Kaleidoscope is a fairly complete
  286. language that can calculate a wide variety of numeric functions. Next up
  287. we'll add another useful expression that is familiar from non-functional
  288. languages...
  289. 'for' Loop Expression
  290. =====================
  291. Now that we know how to add basic control flow constructs to the
  292. language, we have the tools to add more powerful things. Lets add
  293. something more aggressive, a 'for' expression:
  294. ::
  295. extern putchard(char);
  296. def printstar(n)
  297. for i = 1, i < n, 1.0 in
  298. putchard(42); # ascii 42 = '*'
  299. # print 100 '*' characters
  300. printstar(100);
  301. This expression defines a new variable ("i" in this case) which iterates
  302. from a starting value, while the condition ("i < n" in this case) is
  303. true, incrementing by an optional step value ("1.0" in this case). If
  304. the step value is omitted, it defaults to 1.0. While the loop is true,
  305. it executes its body expression. Because we don't have anything better
  306. to return, we'll just define the loop as always returning 0.0. In the
  307. future when we have mutable variables, it will get more useful.
  308. As before, lets talk about the changes that we need to Kaleidoscope to
  309. support this.
  310. Lexer Extensions for the 'for' Loop
  311. -----------------------------------
  312. The lexer extensions are the same sort of thing as for if/then/else:
  313. .. code-block:: ocaml
  314. ... in Token.token ...
  315. (* control *)
  316. | If | Then | Else
  317. | For | In
  318. ... in Lexer.lex_ident...
  319. match Buffer.contents buffer with
  320. | "def" -> [< 'Token.Def; stream >]
  321. | "extern" -> [< 'Token.Extern; stream >]
  322. | "if" -> [< 'Token.If; stream >]
  323. | "then" -> [< 'Token.Then; stream >]
  324. | "else" -> [< 'Token.Else; stream >]
  325. | "for" -> [< 'Token.For; stream >]
  326. | "in" -> [< 'Token.In; stream >]
  327. | id -> [< 'Token.Ident id; stream >]
  328. AST Extensions for the 'for' Loop
  329. ---------------------------------
  330. The AST variant is just as simple. It basically boils down to capturing
  331. the variable name and the constituent expressions in the node.
  332. .. code-block:: ocaml
  333. type expr =
  334. ...
  335. (* variant for for/in. *)
  336. | For of string * expr * expr * expr option * expr
  337. Parser Extensions for the 'for' Loop
  338. ------------------------------------
  339. The parser code is also fairly standard. The only interesting thing here
  340. is handling of the optional step value. The parser code handles it by
  341. checking to see if the second comma is present. If not, it sets the step
  342. value to null in the AST node:
  343. .. code-block:: ocaml
  344. let rec parse_primary = parser
  345. ...
  346. (* forexpr
  347. ::= 'for' identifier '=' expr ',' expr (',' expr)? 'in' expression *)
  348. | [< 'Token.For;
  349. 'Token.Ident id ?? "expected identifier after for";
  350. 'Token.Kwd '=' ?? "expected '=' after for";
  351. stream >] ->
  352. begin parser
  353. | [<
  354. start=parse_expr;
  355. 'Token.Kwd ',' ?? "expected ',' after for";
  356. end_=parse_expr;
  357. stream >] ->
  358. let step =
  359. begin parser
  360. | [< 'Token.Kwd ','; step=parse_expr >] -> Some step
  361. | [< >] -> None
  362. end stream
  363. in
  364. begin parser
  365. | [< 'Token.In; body=parse_expr >] ->
  366. Ast.For (id, start, end_, step, body)
  367. | [< >] ->
  368. raise (Stream.Error "expected 'in' after for")
  369. end stream
  370. | [< >] ->
  371. raise (Stream.Error "expected '=' after for")
  372. end stream
  373. LLVM IR for the 'for' Loop
  374. --------------------------
  375. Now we get to the good part: the LLVM IR we want to generate for this
  376. thing. With the simple example above, we get this LLVM IR (note that
  377. this dump is generated with optimizations disabled for clarity):
  378. .. code-block:: llvm
  379. declare double @putchard(double)
  380. define double @printstar(double %n) {
  381. entry:
  382. ; initial value = 1.0 (inlined into phi)
  383. br label %loop
  384. loop: ; preds = %loop, %entry
  385. %i = phi double [ 1.000000e+00, %entry ], [ %nextvar, %loop ]
  386. ; body
  387. %calltmp = call double @putchard(double 4.200000e+01)
  388. ; increment
  389. %nextvar = fadd double %i, 1.000000e+00
  390. ; termination test
  391. %cmptmp = fcmp ult double %i, %n
  392. %booltmp = uitofp i1 %cmptmp to double
  393. %loopcond = fcmp one double %booltmp, 0.000000e+00
  394. br i1 %loopcond, label %loop, label %afterloop
  395. afterloop: ; preds = %loop
  396. ; loop always returns 0.0
  397. ret double 0.000000e+00
  398. }
  399. This loop contains all the same constructs we saw before: a phi node,
  400. several expressions, and some basic blocks. Lets see how this fits
  401. together.
  402. Code Generation for the 'for' Loop
  403. ----------------------------------
  404. The first part of Codegen is very simple: we just output the start
  405. expression for the loop value:
  406. .. code-block:: ocaml
  407. let rec codegen_expr = function
  408. ...
  409. | Ast.For (var_name, start, end_, step, body) ->
  410. (* Emit the start code first, without 'variable' in scope. *)
  411. let start_val = codegen_expr start in
  412. With this out of the way, the next step is to set up the LLVM basic
  413. block for the start of the loop body. In the case above, the whole loop
  414. body is one block, but remember that the body code itself could consist
  415. of multiple blocks (e.g. if it contains an if/then/else or a for/in
  416. expression).
  417. .. code-block:: ocaml
  418. (* Make the new basic block for the loop header, inserting after current
  419. * block. *)
  420. let preheader_bb = insertion_block builder in
  421. let the_function = block_parent preheader_bb in
  422. let loop_bb = append_block context "loop" the_function in
  423. (* Insert an explicit fall through from the current block to the
  424. * loop_bb. *)
  425. ignore (build_br loop_bb builder);
  426. This code is similar to what we saw for if/then/else. Because we will
  427. need it to create the Phi node, we remember the block that falls through
  428. into the loop. Once we have that, we create the actual block that starts
  429. the loop and create an unconditional branch for the fall-through between
  430. the two blocks.
  431. .. code-block:: ocaml
  432. (* Start insertion in loop_bb. *)
  433. position_at_end loop_bb builder;
  434. (* Start the PHI node with an entry for start. *)
  435. let variable = build_phi [(start_val, preheader_bb)] var_name builder in
  436. Now that the "preheader" for the loop is set up, we switch to emitting
  437. code for the loop body. To begin with, we move the insertion point and
  438. create the PHI node for the loop induction variable. Since we already
  439. know the incoming value for the starting value, we add it to the Phi
  440. node. Note that the Phi will eventually get a second value for the
  441. backedge, but we can't set it up yet (because it doesn't exist!).
  442. .. code-block:: ocaml
  443. (* Within the loop, the variable is defined equal to the PHI node. If it
  444. * shadows an existing variable, we have to restore it, so save it
  445. * now. *)
  446. let old_val =
  447. try Some (Hashtbl.find named_values var_name) with Not_found -> None
  448. in
  449. Hashtbl.add named_values var_name variable;
  450. (* Emit the body of the loop. This, like any other expr, can change the
  451. * current BB. Note that we ignore the value computed by the body, but
  452. * don't allow an error *)
  453. ignore (codegen_expr body);
  454. Now the code starts to get more interesting. Our 'for' loop introduces a
  455. new variable to the symbol table. This means that our symbol table can
  456. now contain either function arguments or loop variables. To handle this,
  457. before we codegen the body of the loop, we add the loop variable as the
  458. current value for its name. Note that it is possible that there is a
  459. variable of the same name in the outer scope. It would be easy to make
  460. this an error (emit an error and return null if there is already an
  461. entry for VarName) but we choose to allow shadowing of variables. In
  462. order to handle this correctly, we remember the Value that we are
  463. potentially shadowing in ``old_val`` (which will be None if there is no
  464. shadowed variable).
  465. Once the loop variable is set into the symbol table, the code
  466. recursively codegen's the body. This allows the body to use the loop
  467. variable: any references to it will naturally find it in the symbol
  468. table.
  469. .. code-block:: ocaml
  470. (* Emit the step value. *)
  471. let step_val =
  472. match step with
  473. | Some step -> codegen_expr step
  474. (* If not specified, use 1.0. *)
  475. | None -> const_float double_type 1.0
  476. in
  477. let next_var = build_add variable step_val "nextvar" builder in
  478. Now that the body is emitted, we compute the next value of the iteration
  479. variable by adding the step value, or 1.0 if it isn't present.
  480. '``next_var``' will be the value of the loop variable on the next
  481. iteration of the loop.
  482. .. code-block:: ocaml
  483. (* Compute the end condition. *)
  484. let end_cond = codegen_expr end_ in
  485. (* Convert condition to a bool by comparing equal to 0.0. *)
  486. let zero = const_float double_type 0.0 in
  487. let end_cond = build_fcmp Fcmp.One end_cond zero "loopcond" builder in
  488. Finally, we evaluate the exit value of the loop, to determine whether
  489. the loop should exit. This mirrors the condition evaluation for the
  490. if/then/else statement.
  491. .. code-block:: ocaml
  492. (* Create the "after loop" block and insert it. *)
  493. let loop_end_bb = insertion_block builder in
  494. let after_bb = append_block context "afterloop" the_function in
  495. (* Insert the conditional branch into the end of loop_end_bb. *)
  496. ignore (build_cond_br end_cond loop_bb after_bb builder);
  497. (* Any new code will be inserted in after_bb. *)
  498. position_at_end after_bb builder;
  499. With the code for the body of the loop complete, we just need to finish
  500. up the control flow for it. This code remembers the end block (for the
  501. phi node), then creates the block for the loop exit ("afterloop"). Based
  502. on the value of the exit condition, it creates a conditional branch that
  503. chooses between executing the loop again and exiting the loop. Any
  504. future code is emitted in the "afterloop" block, so it sets the
  505. insertion position to it.
  506. .. code-block:: ocaml
  507. (* Add a new entry to the PHI node for the backedge. *)
  508. add_incoming (next_var, loop_end_bb) variable;
  509. (* Restore the unshadowed variable. *)
  510. begin match old_val with
  511. | Some old_val -> Hashtbl.add named_values var_name old_val
  512. | None -> ()
  513. end;
  514. (* for expr always returns 0.0. *)
  515. const_null double_type
  516. The final code handles various cleanups: now that we have the
  517. "``next_var``" value, we can add the incoming value to the loop PHI
  518. node. After that, we remove the loop variable from the symbol table, so
  519. that it isn't in scope after the for loop. Finally, code generation of
  520. the for loop always returns 0.0, so that is what we return from
  521. ``Codegen.codegen_expr``.
  522. With this, we conclude the "adding control flow to Kaleidoscope" chapter
  523. of the tutorial. In this chapter we added two control flow constructs,
  524. and used them to motivate a couple of aspects of the LLVM IR that are
  525. important for front-end implementors to know. In the next chapter of our
  526. saga, we will get a bit crazier and add `user-defined
  527. operators <OCamlLangImpl6.html>`_ to our poor innocent language.
  528. Full Code Listing
  529. =================
  530. Here is the complete code listing for our running example, enhanced with
  531. the if/then/else and for expressions.. To build this example, use:
  532. .. code-block:: bash
  533. # Compile
  534. ocamlbuild toy.byte
  535. # Run
  536. ./toy.byte
  537. Here is the code:
  538. \_tags:
  539. ::
  540. <{lexer,parser}.ml>: use_camlp4, pp(camlp4of)
  541. <*.{byte,native}>: g++, use_llvm, use_llvm_analysis
  542. <*.{byte,native}>: use_llvm_executionengine, use_llvm_target
  543. <*.{byte,native}>: use_llvm_scalar_opts, use_bindings
  544. myocamlbuild.ml:
  545. .. code-block:: ocaml
  546. open Ocamlbuild_plugin;;
  547. ocaml_lib ~extern:true "llvm";;
  548. ocaml_lib ~extern:true "llvm_analysis";;
  549. ocaml_lib ~extern:true "llvm_executionengine";;
  550. ocaml_lib ~extern:true "llvm_target";;
  551. ocaml_lib ~extern:true "llvm_scalar_opts";;
  552. flag ["link"; "ocaml"; "g++"] (S[A"-cc"; A"g++"]);;
  553. dep ["link"; "ocaml"; "use_bindings"] ["bindings.o"];;
  554. token.ml:
  555. .. code-block:: ocaml
  556. (*===----------------------------------------------------------------------===
  557. * Lexer Tokens
  558. *===----------------------------------------------------------------------===*)
  559. (* The lexer returns these 'Kwd' if it is an unknown character, otherwise one of
  560. * these others for known things. *)
  561. type token =
  562. (* commands *)
  563. | Def | Extern
  564. (* primary *)
  565. | Ident of string | Number of float
  566. (* unknown *)
  567. | Kwd of char
  568. (* control *)
  569. | If | Then | Else
  570. | For | In
  571. lexer.ml:
  572. .. code-block:: ocaml
  573. (*===----------------------------------------------------------------------===
  574. * Lexer
  575. *===----------------------------------------------------------------------===*)
  576. let rec lex = parser
  577. (* Skip any whitespace. *)
  578. | [< ' (' ' | '\n' | '\r' | '\t'); stream >] -> lex stream
  579. (* identifier: [a-zA-Z][a-zA-Z0-9] *)
  580. | [< ' ('A' .. 'Z' | 'a' .. 'z' as c); stream >] ->
  581. let buffer = Buffer.create 1 in
  582. Buffer.add_char buffer c;
  583. lex_ident buffer stream
  584. (* number: [0-9.]+ *)
  585. | [< ' ('0' .. '9' as c); stream >] ->
  586. let buffer = Buffer.create 1 in
  587. Buffer.add_char buffer c;
  588. lex_number buffer stream
  589. (* Comment until end of line. *)
  590. | [< ' ('#'); stream >] ->
  591. lex_comment stream
  592. (* Otherwise, just return the character as its ascii value. *)
  593. | [< 'c; stream >] ->
  594. [< 'Token.Kwd c; lex stream >]
  595. (* end of stream. *)
  596. | [< >] -> [< >]
  597. and lex_number buffer = parser
  598. | [< ' ('0' .. '9' | '.' as c); stream >] ->
  599. Buffer.add_char buffer c;
  600. lex_number buffer stream
  601. | [< stream=lex >] ->
  602. [< 'Token.Number (float_of_string (Buffer.contents buffer)); stream >]
  603. and lex_ident buffer = parser
  604. | [< ' ('A' .. 'Z' | 'a' .. 'z' | '0' .. '9' as c); stream >] ->
  605. Buffer.add_char buffer c;
  606. lex_ident buffer stream
  607. | [< stream=lex >] ->
  608. match Buffer.contents buffer with
  609. | "def" -> [< 'Token.Def; stream >]
  610. | "extern" -> [< 'Token.Extern; stream >]
  611. | "if" -> [< 'Token.If; stream >]
  612. | "then" -> [< 'Token.Then; stream >]
  613. | "else" -> [< 'Token.Else; stream >]
  614. | "for" -> [< 'Token.For; stream >]
  615. | "in" -> [< 'Token.In; stream >]
  616. | id -> [< 'Token.Ident id; stream >]
  617. and lex_comment = parser
  618. | [< ' ('\n'); stream=lex >] -> stream
  619. | [< 'c; e=lex_comment >] -> e
  620. | [< >] -> [< >]
  621. ast.ml:
  622. .. code-block:: ocaml
  623. (*===----------------------------------------------------------------------===
  624. * Abstract Syntax Tree (aka Parse Tree)
  625. *===----------------------------------------------------------------------===*)
  626. (* expr - Base type for all expression nodes. *)
  627. type expr =
  628. (* variant for numeric literals like "1.0". *)
  629. | Number of float
  630. (* variant for referencing a variable, like "a". *)
  631. | Variable of string
  632. (* variant for a binary operator. *)
  633. | Binary of char * expr * expr
  634. (* variant for function calls. *)
  635. | Call of string * expr array
  636. (* variant for if/then/else. *)
  637. | If of expr * expr * expr
  638. (* variant for for/in. *)
  639. | For of string * expr * expr * expr option * expr
  640. (* proto - This type represents the "prototype" for a function, which captures
  641. * its name, and its argument names (thus implicitly the number of arguments the
  642. * function takes). *)
  643. type proto = Prototype of string * string array
  644. (* func - This type represents a function definition itself. *)
  645. type func = Function of proto * expr
  646. parser.ml:
  647. .. code-block:: ocaml
  648. (*===---------------------------------------------------------------------===
  649. * Parser
  650. *===---------------------------------------------------------------------===*)
  651. (* binop_precedence - This holds the precedence for each binary operator that is
  652. * defined *)
  653. let binop_precedence:(char, int) Hashtbl.t = Hashtbl.create 10
  654. (* precedence - Get the precedence of the pending binary operator token. *)
  655. let precedence c = try Hashtbl.find binop_precedence c with Not_found -> -1
  656. (* primary
  657. * ::= identifier
  658. * ::= numberexpr
  659. * ::= parenexpr
  660. * ::= ifexpr
  661. * ::= forexpr *)
  662. let rec parse_primary = parser
  663. (* numberexpr ::= number *)
  664. | [< 'Token.Number n >] -> Ast.Number n
  665. (* parenexpr ::= '(' expression ')' *)
  666. | [< 'Token.Kwd '('; e=parse_expr; 'Token.Kwd ')' ?? "expected ')'" >] -> e
  667. (* identifierexpr
  668. * ::= identifier
  669. * ::= identifier '(' argumentexpr ')' *)
  670. | [< 'Token.Ident id; stream >] ->
  671. let rec parse_args accumulator = parser
  672. | [< e=parse_expr; stream >] ->
  673. begin parser
  674. | [< 'Token.Kwd ','; e=parse_args (e :: accumulator) >] -> e
  675. | [< >] -> e :: accumulator
  676. end stream
  677. | [< >] -> accumulator
  678. in
  679. let rec parse_ident id = parser
  680. (* Call. *)
  681. | [< 'Token.Kwd '(';
  682. args=parse_args [];
  683. 'Token.Kwd ')' ?? "expected ')'">] ->
  684. Ast.Call (id, Array.of_list (List.rev args))
  685. (* Simple variable ref. *)
  686. | [< >] -> Ast.Variable id
  687. in
  688. parse_ident id stream
  689. (* ifexpr ::= 'if' expr 'then' expr 'else' expr *)
  690. | [< 'Token.If; c=parse_expr;
  691. 'Token.Then ?? "expected 'then'"; t=parse_expr;
  692. 'Token.Else ?? "expected 'else'"; e=parse_expr >] ->
  693. Ast.If (c, t, e)
  694. (* forexpr
  695. ::= 'for' identifier '=' expr ',' expr (',' expr)? 'in' expression *)
  696. | [< 'Token.For;
  697. 'Token.Ident id ?? "expected identifier after for";
  698. 'Token.Kwd '=' ?? "expected '=' after for";
  699. stream >] ->
  700. begin parser
  701. | [<
  702. start=parse_expr;
  703. 'Token.Kwd ',' ?? "expected ',' after for";
  704. end_=parse_expr;
  705. stream >] ->
  706. let step =
  707. begin parser
  708. | [< 'Token.Kwd ','; step=parse_expr >] -> Some step
  709. | [< >] -> None
  710. end stream
  711. in
  712. begin parser
  713. | [< 'Token.In; body=parse_expr >] ->
  714. Ast.For (id, start, end_, step, body)
  715. | [< >] ->
  716. raise (Stream.Error "expected 'in' after for")
  717. end stream
  718. | [< >] ->
  719. raise (Stream.Error "expected '=' after for")
  720. end stream
  721. | [< >] -> raise (Stream.Error "unknown token when expecting an expression.")
  722. (* binoprhs
  723. * ::= ('+' primary)* *)
  724. and parse_bin_rhs expr_prec lhs stream =
  725. match Stream.peek stream with
  726. (* If this is a binop, find its precedence. *)
  727. | Some (Token.Kwd c) when Hashtbl.mem binop_precedence c ->
  728. let token_prec = precedence c in
  729. (* If this is a binop that binds at least as tightly as the current binop,
  730. * consume it, otherwise we are done. *)
  731. if token_prec < expr_prec then lhs else begin
  732. (* Eat the binop. *)
  733. Stream.junk stream;
  734. (* Parse the primary expression after the binary operator. *)
  735. let rhs = parse_primary stream in
  736. (* Okay, we know this is a binop. *)
  737. let rhs =
  738. match Stream.peek stream with
  739. | Some (Token.Kwd c2) ->
  740. (* If BinOp binds less tightly with rhs than the operator after
  741. * rhs, let the pending operator take rhs as its lhs. *)
  742. let next_prec = precedence c2 in
  743. if token_prec < next_prec
  744. then parse_bin_rhs (token_prec + 1) rhs stream
  745. else rhs
  746. | _ -> rhs
  747. in
  748. (* Merge lhs/rhs. *)
  749. let lhs = Ast.Binary (c, lhs, rhs) in
  750. parse_bin_rhs expr_prec lhs stream
  751. end
  752. | _ -> lhs
  753. (* expression
  754. * ::= primary binoprhs *)
  755. and parse_expr = parser
  756. | [< lhs=parse_primary; stream >] -> parse_bin_rhs 0 lhs stream
  757. (* prototype
  758. * ::= id '(' id* ')' *)
  759. let parse_prototype =
  760. let rec parse_args accumulator = parser
  761. | [< 'Token.Ident id; e=parse_args (id::accumulator) >] -> e
  762. | [< >] -> accumulator
  763. in
  764. parser
  765. | [< 'Token.Ident id;
  766. 'Token.Kwd '(' ?? "expected '(' in prototype";
  767. args=parse_args [];
  768. 'Token.Kwd ')' ?? "expected ')' in prototype" >] ->
  769. (* success. *)
  770. Ast.Prototype (id, Array.of_list (List.rev args))
  771. | [< >] ->
  772. raise (Stream.Error "expected function name in prototype")
  773. (* definition ::= 'def' prototype expression *)
  774. let parse_definition = parser
  775. | [< 'Token.Def; p=parse_prototype; e=parse_expr >] ->
  776. Ast.Function (p, e)
  777. (* toplevelexpr ::= expression *)
  778. let parse_toplevel = parser
  779. | [< e=parse_expr >] ->
  780. (* Make an anonymous proto. *)
  781. Ast.Function (Ast.Prototype ("", [||]), e)
  782. (* external ::= 'extern' prototype *)
  783. let parse_extern = parser
  784. | [< 'Token.Extern; e=parse_prototype >] -> e
  785. codegen.ml:
  786. .. code-block:: ocaml
  787. (*===----------------------------------------------------------------------===
  788. * Code Generation
  789. *===----------------------------------------------------------------------===*)
  790. open Llvm
  791. exception Error of string
  792. let context = global_context ()
  793. let the_module = create_module context "my cool jit"
  794. let builder = builder context
  795. let named_values:(string, llvalue) Hashtbl.t = Hashtbl.create 10
  796. let double_type = double_type context
  797. let rec codegen_expr = function
  798. | Ast.Number n -> const_float double_type n
  799. | Ast.Variable name ->
  800. (try Hashtbl.find named_values name with
  801. | Not_found -> raise (Error "unknown variable name"))
  802. | Ast.Binary (op, lhs, rhs) ->
  803. let lhs_val = codegen_expr lhs in
  804. let rhs_val = codegen_expr rhs in
  805. begin
  806. match op with
  807. | '+' -> build_add lhs_val rhs_val "addtmp" builder
  808. | '-' -> build_sub lhs_val rhs_val "subtmp" builder
  809. | '*' -> build_mul lhs_val rhs_val "multmp" builder
  810. | '<' ->
  811. (* Convert bool 0/1 to double 0.0 or 1.0 *)
  812. let i = build_fcmp Fcmp.Ult lhs_val rhs_val "cmptmp" builder in
  813. build_uitofp i double_type "booltmp" builder
  814. | _ -> raise (Error "invalid binary operator")
  815. end
  816. | Ast.Call (callee, args) ->
  817. (* Look up the name in the module table. *)
  818. let callee =
  819. match lookup_function callee the_module with
  820. | Some callee -> callee
  821. | None -> raise (Error "unknown function referenced")
  822. in
  823. let params = params callee in
  824. (* If argument mismatch error. *)
  825. if Array.length params == Array.length args then () else
  826. raise (Error "incorrect # arguments passed");
  827. let args = Array.map codegen_expr args in
  828. build_call callee args "calltmp" builder
  829. | Ast.If (cond, then_, else_) ->
  830. let cond = codegen_expr cond in
  831. (* Convert condition to a bool by comparing equal to 0.0 *)
  832. let zero = const_float double_type 0.0 in
  833. let cond_val = build_fcmp Fcmp.One cond zero "ifcond" builder in
  834. (* Grab the first block so that we might later add the conditional branch
  835. * to it at the end of the function. *)
  836. let start_bb = insertion_block builder in
  837. let the_function = block_parent start_bb in
  838. let then_bb = append_block context "then" the_function in
  839. (* Emit 'then' value. *)
  840. position_at_end then_bb builder;
  841. let then_val = codegen_expr then_ in
  842. (* Codegen of 'then' can change the current block, update then_bb for the
  843. * phi. We create a new name because one is used for the phi node, and the
  844. * other is used for the conditional branch. *)
  845. let new_then_bb = insertion_block builder in
  846. (* Emit 'else' value. *)
  847. let else_bb = append_block context "else" the_function in
  848. position_at_end else_bb builder;
  849. let else_val = codegen_expr else_ in
  850. (* Codegen of 'else' can change the current block, update else_bb for the
  851. * phi. *)
  852. let new_else_bb = insertion_block builder in
  853. (* Emit merge block. *)
  854. let merge_bb = append_block context "ifcont" the_function in
  855. position_at_end merge_bb builder;
  856. let incoming = [(then_val, new_then_bb); (else_val, new_else_bb)] in
  857. let phi = build_phi incoming "iftmp" builder in
  858. (* Return to the start block to add the conditional branch. *)
  859. position_at_end start_bb builder;
  860. ignore (build_cond_br cond_val then_bb else_bb builder);
  861. (* Set a unconditional branch at the end of the 'then' block and the
  862. * 'else' block to the 'merge' block. *)
  863. position_at_end new_then_bb builder; ignore (build_br merge_bb builder);
  864. position_at_end new_else_bb builder; ignore (build_br merge_bb builder);
  865. (* Finally, set the builder to the end of the merge block. *)
  866. position_at_end merge_bb builder;
  867. phi
  868. | Ast.For (var_name, start, end_, step, body) ->
  869. (* Emit the start code first, without 'variable' in scope. *)
  870. let start_val = codegen_expr start in
  871. (* Make the new basic block for the loop header, inserting after current
  872. * block. *)
  873. let preheader_bb = insertion_block builder in
  874. let the_function = block_parent preheader_bb in
  875. let loop_bb = append_block context "loop" the_function in
  876. (* Insert an explicit fall through from the current block to the
  877. * loop_bb. *)
  878. ignore (build_br loop_bb builder);
  879. (* Start insertion in loop_bb. *)
  880. position_at_end loop_bb builder;
  881. (* Start the PHI node with an entry for start. *)
  882. let variable = build_phi [(start_val, preheader_bb)] var_name builder in
  883. (* Within the loop, the variable is defined equal to the PHI node. If it
  884. * shadows an existing variable, we have to restore it, so save it
  885. * now. *)
  886. let old_val =
  887. try Some (Hashtbl.find named_values var_name) with Not_found -> None
  888. in
  889. Hashtbl.add named_values var_name variable;
  890. (* Emit the body of the loop. This, like any other expr, can change the
  891. * current BB. Note that we ignore the value computed by the body, but
  892. * don't allow an error *)
  893. ignore (codegen_expr body);
  894. (* Emit the step value. *)
  895. let step_val =
  896. match step with
  897. | Some step -> codegen_expr step
  898. (* If not specified, use 1.0. *)
  899. | None -> const_float double_type 1.0
  900. in
  901. let next_var = build_add variable step_val "nextvar" builder in
  902. (* Compute the end condition. *)
  903. let end_cond = codegen_expr end_ in
  904. (* Convert condition to a bool by comparing equal to 0.0. *)
  905. let zero = const_float double_type 0.0 in
  906. let end_cond = build_fcmp Fcmp.One end_cond zero "loopcond" builder in
  907. (* Create the "after loop" block and insert it. *)
  908. let loop_end_bb = insertion_block builder in
  909. let after_bb = append_block context "afterloop" the_function in
  910. (* Insert the conditional branch into the end of loop_end_bb. *)
  911. ignore (build_cond_br end_cond loop_bb after_bb builder);
  912. (* Any new code will be inserted in after_bb. *)
  913. position_at_end after_bb builder;
  914. (* Add a new entry to the PHI node for the backedge. *)
  915. add_incoming (next_var, loop_end_bb) variable;
  916. (* Restore the unshadowed variable. *)
  917. begin match old_val with
  918. | Some old_val -> Hashtbl.add named_values var_name old_val
  919. | None -> ()
  920. end;
  921. (* for expr always returns 0.0. *)
  922. const_null double_type
  923. let codegen_proto = function
  924. | Ast.Prototype (name, args) ->
  925. (* Make the function type: double(double,double) etc. *)
  926. let doubles = Array.make (Array.length args) double_type in
  927. let ft = function_type double_type doubles in
  928. let f =
  929. match lookup_function name the_module with
  930. | None -> declare_function name ft the_module
  931. (* If 'f' conflicted, there was already something named 'name'. If it
  932. * has a body, don't allow redefinition or reextern. *)
  933. | Some f ->
  934. (* If 'f' already has a body, reject this. *)
  935. if block_begin f <> At_end f then
  936. raise (Error "redefinition of function");
  937. (* If 'f' took a different number of arguments, reject. *)
  938. if element_type (type_of f) <> ft then
  939. raise (Error "redefinition of function with different # args");
  940. f
  941. in
  942. (* Set names for all arguments. *)
  943. Array.iteri (fun i a ->
  944. let n = args.(i) in
  945. set_value_name n a;
  946. Hashtbl.add named_values n a;
  947. ) (params f);
  948. f
  949. let codegen_func the_fpm = function
  950. | Ast.Function (proto, body) ->
  951. Hashtbl.clear named_values;
  952. let the_function = codegen_proto proto in
  953. (* Create a new basic block to start insertion into. *)
  954. let bb = append_block context "entry" the_function in
  955. position_at_end bb builder;
  956. try
  957. let ret_val = codegen_expr body in
  958. (* Finish off the function. *)
  959. let _ = build_ret ret_val builder in
  960. (* Validate the generated code, checking for consistency. *)
  961. Llvm_analysis.assert_valid_function the_function;
  962. (* Optimize the function. *)
  963. let _ = PassManager.run_function the_function the_fpm in
  964. the_function
  965. with e ->
  966. delete_function the_function;
  967. raise e
  968. toplevel.ml:
  969. .. code-block:: ocaml
  970. (*===----------------------------------------------------------------------===
  971. * Top-Level parsing and JIT Driver
  972. *===----------------------------------------------------------------------===*)
  973. open Llvm
  974. open Llvm_executionengine
  975. (* top ::= definition | external | expression | ';' *)
  976. let rec main_loop the_fpm the_execution_engine stream =
  977. match Stream.peek stream with
  978. | None -> ()
  979. (* ignore top-level semicolons. *)
  980. | Some (Token.Kwd ';') ->
  981. Stream.junk stream;
  982. main_loop the_fpm the_execution_engine stream
  983. | Some token ->
  984. begin
  985. try match token with
  986. | Token.Def ->
  987. let e = Parser.parse_definition stream in
  988. print_endline "parsed a function definition.";
  989. dump_value (Codegen.codegen_func the_fpm e);
  990. | Token.Extern ->
  991. let e = Parser.parse_extern stream in
  992. print_endline "parsed an extern.";
  993. dump_value (Codegen.codegen_proto e);
  994. | _ ->
  995. (* Evaluate a top-level expression into an anonymous function. *)
  996. let e = Parser.parse_toplevel stream in
  997. print_endline "parsed a top-level expr";
  998. let the_function = Codegen.codegen_func the_fpm e in
  999. dump_value the_function;
  1000. (* JIT the function, returning a function pointer. *)
  1001. let result = ExecutionEngine.run_function the_function [||]
  1002. the_execution_engine in
  1003. print_string "Evaluated to ";
  1004. print_float (GenericValue.as_float Codegen.double_type result);
  1005. print_newline ();
  1006. with Stream.Error s | Codegen.Error s ->
  1007. (* Skip token for error recovery. *)
  1008. Stream.junk stream;
  1009. print_endline s;
  1010. end;
  1011. print_string "ready> "; flush stdout;
  1012. main_loop the_fpm the_execution_engine stream
  1013. toy.ml:
  1014. .. code-block:: ocaml
  1015. (*===----------------------------------------------------------------------===
  1016. * Main driver code.
  1017. *===----------------------------------------------------------------------===*)
  1018. open Llvm
  1019. open Llvm_executionengine
  1020. open Llvm_target
  1021. open Llvm_scalar_opts
  1022. let main () =
  1023. ignore (initialize_native_target ());
  1024. (* Install standard binary operators.
  1025. * 1 is the lowest precedence. *)
  1026. Hashtbl.add Parser.binop_precedence '<' 10;
  1027. Hashtbl.add Parser.binop_precedence '+' 20;
  1028. Hashtbl.add Parser.binop_precedence '-' 20;
  1029. Hashtbl.add Parser.binop_precedence '*' 40; (* highest. *)
  1030. (* Prime the first token. *)
  1031. print_string "ready> "; flush stdout;
  1032. let stream = Lexer.lex (Stream.of_channel stdin) in
  1033. (* Create the JIT. *)
  1034. let the_execution_engine = ExecutionEngine.create Codegen.the_module in
  1035. let the_fpm = PassManager.create_function Codegen.the_module in
  1036. (* Set up the optimizer pipeline. Start with registering info about how the
  1037. * target lays out data structures. *)
  1038. DataLayout.add (ExecutionEngine.target_data the_execution_engine) the_fpm;
  1039. (* Do simple "peephole" optimizations and bit-twiddling optzn. *)
  1040. add_instruction_combination the_fpm;
  1041. (* reassociate expressions. *)
  1042. add_reassociation the_fpm;
  1043. (* Eliminate Common SubExpressions. *)
  1044. add_gvn the_fpm;
  1045. (* Simplify the control flow graph (deleting unreachable blocks, etc). *)
  1046. add_cfg_simplification the_fpm;
  1047. ignore (PassManager.initialize the_fpm);
  1048. (* Run the main "interpreter loop" now. *)
  1049. Toplevel.main_loop the_fpm the_execution_engine stream;
  1050. (* Print out all the generated code. *)
  1051. dump_module Codegen.the_module
  1052. ;;
  1053. main ()
  1054. bindings.c
  1055. .. code-block:: c
  1056. #include <stdio.h>
  1057. /* putchard - putchar that takes a double and returns 0. */
  1058. extern double putchard(double X) {
  1059. putchar((char)X);
  1060. return 0;
  1061. }
  1062. `Next: Extending the language: user-defined
  1063. operators <OCamlLangImpl6.html>`_