[www-releases] r290368 - Add 3.9.1 docs.

Tom Stellard via llvm-commits llvm-commits at lists.llvm.org
Thu Dec 22 12:04:06 PST 2016


Added: www-releases/trunk/3.9.1/docs/_sources/tutorial/OCamlLangImpl5.txt
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_sources/tutorial/OCamlLangImpl5.txt?rev=290368&view=auto
==============================================================================
--- www-releases/trunk/3.9.1/docs/_sources/tutorial/OCamlLangImpl5.txt (added)
+++ www-releases/trunk/3.9.1/docs/_sources/tutorial/OCamlLangImpl5.txt Thu Dec 22 14:04:03 2016
@@ -0,0 +1,1362 @@
+==================================================
+Kaleidoscope: Extending the Language: Control Flow
+==================================================
+
+.. contents::
+   :local:
+
+Chapter 5 Introduction
+======================
+
+Welcome to Chapter 5 of the "`Implementing a language with
+LLVM <index.html>`_" tutorial. Parts 1-4 described the implementation of
+the simple Kaleidoscope language and included support for generating
+LLVM IR, followed by optimizations and a JIT compiler. Unfortunately, as
+presented, Kaleidoscope is mostly useless: it has no control flow other
+than call and return. This means that you can't have conditional
+branches in the code, significantly limiting its power. In this episode
+of "build that compiler", we'll extend Kaleidoscope to have an
+if/then/else expression plus a simple 'for' loop.
+
+If/Then/Else
+============
+
+Extending Kaleidoscope to support if/then/else is quite straightforward.
+It basically requires adding lexer support for this "new" concept to the
+lexer, parser, AST, and LLVM code emitter. This example is nice, because
+it shows how easy it is to "grow" a language over time, incrementally
+extending it as new ideas are discovered.
+
+Before we get going on "how" we add this extension, lets talk about
+"what" we want. The basic idea is that we want to be able to write this
+sort of thing:
+
+::
+
+    def fib(x)
+      if x < 3 then
+        1
+      else
+        fib(x-1)+fib(x-2);
+
+In Kaleidoscope, every construct is an expression: there are no
+statements. As such, the if/then/else expression needs to return a value
+like any other. Since we're using a mostly functional form, we'll have
+it evaluate its conditional, then return the 'then' or 'else' value
+based on how the condition was resolved. This is very similar to the C
+"?:" expression.
+
+The semantics of the if/then/else expression is that it evaluates the
+condition to a boolean equality value: 0.0 is considered to be false and
+everything else is considered to be true. If the condition is true, the
+first subexpression is evaluated and returned, if the condition is
+false, the second subexpression is evaluated and returned. Since
+Kaleidoscope allows side-effects, this behavior is important to nail
+down.
+
+Now that we know what we "want", lets break this down into its
+constituent pieces.
+
+Lexer Extensions for If/Then/Else
+---------------------------------
+
+The lexer extensions are straightforward. First we add new variants for
+the relevant tokens:
+
+.. code-block:: ocaml
+
+      (* control *)
+      | If | Then | Else | For | In
+
+Once we have that, we recognize the new keywords in the lexer. This is
+pretty simple stuff:
+
+.. code-block:: ocaml
+
+          ...
+          match Buffer.contents buffer with
+          | "def" -> [< 'Token.Def; stream >]
+          | "extern" -> [< 'Token.Extern; stream >]
+          | "if" -> [< 'Token.If; stream >]
+          | "then" -> [< 'Token.Then; stream >]
+          | "else" -> [< 'Token.Else; stream >]
+          | "for" -> [< 'Token.For; stream >]
+          | "in" -> [< 'Token.In; stream >]
+          | id -> [< 'Token.Ident id; stream >]
+
+AST Extensions for If/Then/Else
+-------------------------------
+
+To represent the new expression we add a new AST variant for it:
+
+.. code-block:: ocaml
+
+    type expr =
+      ...
+      (* variant for if/then/else. *)
+      | If of expr * expr * expr
+
+The AST variant just has pointers to the various subexpressions.
+
+Parser Extensions for If/Then/Else
+----------------------------------
+
+Now that we have the relevant tokens coming from the lexer and we have
+the AST node to build, our parsing logic is relatively straightforward.
+First we define a new parsing function:
+
+.. code-block:: ocaml
+
+    let rec parse_primary = parser
+      ...
+      (* ifexpr ::= 'if' expr 'then' expr 'else' expr *)
+      | [< 'Token.If; c=parse_expr;
+           'Token.Then ?? "expected 'then'"; t=parse_expr;
+           'Token.Else ?? "expected 'else'"; e=parse_expr >] ->
+          Ast.If (c, t, e)
+
+Next we hook it up as a primary expression:
+
+.. code-block:: ocaml
+
+    let rec parse_primary = parser
+      ...
+      (* ifexpr ::= 'if' expr 'then' expr 'else' expr *)
+      | [< 'Token.If; c=parse_expr;
+           'Token.Then ?? "expected 'then'"; t=parse_expr;
+           'Token.Else ?? "expected 'else'"; e=parse_expr >] ->
+          Ast.If (c, t, e)
+
+LLVM IR for If/Then/Else
+------------------------
+
+Now that we have it parsing and building the AST, the final piece is
+adding LLVM code generation support. This is the most interesting part
+of the if/then/else example, because this is where it starts to
+introduce new concepts. All of the code above has been thoroughly
+described in previous chapters.
+
+To motivate the code we want to produce, lets take a look at a simple
+example. Consider:
+
+::
+
+    extern foo();
+    extern bar();
+    def baz(x) if x then foo() else bar();
+
+If you disable optimizations, the code you'll (soon) get from
+Kaleidoscope looks like this:
+
+.. code-block:: llvm
+
+    declare double @foo()
+
+    declare double @bar()
+
+    define double @baz(double %x) {
+    entry:
+      %ifcond = fcmp one double %x, 0.000000e+00
+      br i1 %ifcond, label %then, label %else
+
+    then:    ; preds = %entry
+      %calltmp = call double @foo()
+      br label %ifcont
+
+    else:    ; preds = %entry
+      %calltmp1 = call double @bar()
+      br label %ifcont
+
+    ifcont:    ; preds = %else, %then
+      %iftmp = phi double [ %calltmp, %then ], [ %calltmp1, %else ]
+      ret double %iftmp
+    }
+
+To visualize the control flow graph, you can use a nifty feature of the
+LLVM '`opt <http://llvm.org/cmds/opt.html>`_' tool. If you put this LLVM
+IR into "t.ll" and run "``llvm-as < t.ll | opt -analyze -view-cfg``", `a
+window will pop up <../ProgrammersManual.html#viewing-graphs-while-debugging-code>`_ and you'll
+see this graph:
+
+.. figure:: LangImpl05-cfg.png
+   :align: center
+   :alt: Example CFG
+
+   Example CFG
+
+Another way to get this is to call
+"``Llvm_analysis.view_function_cfg f``" or
+"``Llvm_analysis.view_function_cfg_only f``" (where ``f`` is a
+"``Function``") either by inserting actual calls into the code and
+recompiling or by calling these in the debugger. LLVM has many nice
+features for visualizing various graphs.
+
+Getting back to the generated code, it is fairly simple: the entry block
+evaluates the conditional expression ("x" in our case here) and compares
+the result to 0.0 with the "``fcmp one``" instruction ('one' is "Ordered
+and Not Equal"). Based on the result of this expression, the code jumps
+to either the "then" or "else" blocks, which contain the expressions for
+the true/false cases.
+
+Once the then/else blocks are finished executing, they both branch back
+to the 'ifcont' block to execute the code that happens after the
+if/then/else. In this case the only thing left to do is to return to the
+caller of the function. The question then becomes: how does the code
+know which expression to return?
+
+The answer to this question involves an important SSA operation: the
+`Phi
+operation <http://en.wikipedia.org/wiki/Static_single_assignment_form>`_.
+If you're not familiar with SSA, `the wikipedia
+article <http://en.wikipedia.org/wiki/Static_single_assignment_form>`_
+is a good introduction and there are various other introductions to it
+available on your favorite search engine. The short version is that
+"execution" of the Phi operation requires "remembering" which block
+control came from. The Phi operation takes on the value corresponding to
+the input control block. In this case, if control comes in from the
+"then" block, it gets the value of "calltmp". If control comes from the
+"else" block, it gets the value of "calltmp1".
+
+At this point, you are probably starting to think "Oh no! This means my
+simple and elegant front-end will have to start generating SSA form in
+order to use LLVM!". Fortunately, this is not the case, and we strongly
+advise *not* implementing an SSA construction algorithm in your
+front-end unless there is an amazingly good reason to do so. In
+practice, there are two sorts of values that float around in code
+written for your average imperative programming language that might need
+Phi nodes:
+
+#. Code that involves user variables: ``x = 1; x = x + 1;``
+#. Values that are implicit in the structure of your AST, such as the
+   Phi node in this case.
+
+In `Chapter 7 <OCamlLangImpl7.html>`_ of this tutorial ("mutable
+variables"), we'll talk about #1 in depth. For now, just believe me that
+you don't need SSA construction to handle this case. For #2, you have
+the choice of using the techniques that we will describe for #1, or you
+can insert Phi nodes directly, if convenient. In this case, it is really
+really easy to generate the Phi node, so we choose to do it directly.
+
+Okay, enough of the motivation and overview, lets generate code!
+
+Code Generation for If/Then/Else
+--------------------------------
+
+In order to generate code for this, we implement the ``Codegen`` method
+for ``IfExprAST``:
+
+.. code-block:: ocaml
+
+    let rec codegen_expr = function
+      ...
+      | Ast.If (cond, then_, else_) ->
+          let cond = codegen_expr cond in
+
+          (* Convert condition to a bool by comparing equal to 0.0 *)
+          let zero = const_float double_type 0.0 in
+          let cond_val = build_fcmp Fcmp.One cond zero "ifcond" builder in
+
+This code is straightforward and similar to what we saw before. We emit
+the expression for the condition, then compare that value to zero to get
+a truth value as a 1-bit (bool) value.
+
+.. code-block:: ocaml
+
+          (* Grab the first block so that we might later add the conditional branch
+           * to it at the end of the function. *)
+          let start_bb = insertion_block builder in
+          let the_function = block_parent start_bb in
+
+          let then_bb = append_block context "then" the_function in
+          position_at_end then_bb builder;
+
+As opposed to the `C++ tutorial <LangImpl5.html>`_, we have to build our
+basic blocks bottom up since we can't have dangling BasicBlocks. We
+start off by saving a pointer to the first block (which might not be the
+entry block), which we'll need to build a conditional branch later. We
+do this by asking the ``builder`` for the current BasicBlock. The fourth
+line gets the current Function object that is being built. It gets this
+by the ``start_bb`` for its "parent" (the function it is currently
+embedded into).
+
+Once it has that, it creates one block. It is automatically appended
+into the function's list of blocks.
+
+.. code-block:: ocaml
+
+          (* Emit 'then' value. *)
+          position_at_end then_bb builder;
+          let then_val = codegen_expr then_ in
+
+          (* Codegen of 'then' can change the current block, update then_bb for the
+           * phi. We create a new name because one is used for the phi node, and the
+           * other is used for the conditional branch. *)
+          let new_then_bb = insertion_block builder in
+
+We move the builder to start inserting into the "then" block. Strictly
+speaking, this call moves the insertion point to be at the end of the
+specified block. However, since the "then" block is empty, it also
+starts out by inserting at the beginning of the block. :)
+
+Once the insertion point is set, we recursively codegen the "then"
+expression from the AST.
+
+The final line here is quite subtle, but is very important. The basic
+issue is that when we create the Phi node in the merge block, we need to
+set up the block/value pairs that indicate how the Phi will work.
+Importantly, the Phi node expects to have an entry for each predecessor
+of the block in the CFG. Why then, are we getting the current block when
+we just set it to ThenBB 5 lines above? The problem is that the "Then"
+expression may actually itself change the block that the Builder is
+emitting into if, for example, it contains a nested "if/then/else"
+expression. Because calling Codegen recursively could arbitrarily change
+the notion of the current block, we are required to get an up-to-date
+value for code that will set up the Phi node.
+
+.. code-block:: ocaml
+
+          (* Emit 'else' value. *)
+          let else_bb = append_block context "else" the_function in
+          position_at_end else_bb builder;
+          let else_val = codegen_expr else_ in
+
+          (* Codegen of 'else' can change the current block, update else_bb for the
+           * phi. *)
+          let new_else_bb = insertion_block builder in
+
+Code generation for the 'else' block is basically identical to codegen
+for the 'then' block.
+
+.. code-block:: ocaml
+
+          (* Emit merge block. *)
+          let merge_bb = append_block context "ifcont" the_function in
+          position_at_end merge_bb builder;
+          let incoming = [(then_val, new_then_bb); (else_val, new_else_bb)] in
+          let phi = build_phi incoming "iftmp" builder in
+
+The first two lines here are now familiar: the first adds the "merge"
+block to the Function object. The second changes the insertion
+point so that newly created code will go into the "merge" block. Once
+that is done, we need to create the PHI node and set up the block/value
+pairs for the PHI.
+
+.. code-block:: ocaml
+
+          (* Return to the start block to add the conditional branch. *)
+          position_at_end start_bb builder;
+          ignore (build_cond_br cond_val then_bb else_bb builder);
+
+Once the blocks are created, we can emit the conditional branch that
+chooses between them. Note that creating new blocks does not implicitly
+affect the IRBuilder, so it is still inserting into the block that the
+condition went into. This is why we needed to save the "start" block.
+
+.. code-block:: ocaml
+
+          (* Set a unconditional branch at the end of the 'then' block and the
+           * 'else' block to the 'merge' block. *)
+          position_at_end new_then_bb builder; ignore (build_br merge_bb builder);
+          position_at_end new_else_bb builder; ignore (build_br merge_bb builder);
+
+          (* Finally, set the builder to the end of the merge block. *)
+          position_at_end merge_bb builder;
+
+          phi
+
+To finish off the blocks, we create an unconditional branch to the merge
+block. One interesting (and very important) aspect of the LLVM IR is
+that it `requires all basic blocks to be
+"terminated" <../LangRef.html#functionstructure>`_ with a `control flow
+instruction <../LangRef.html#terminators>`_ such as return or branch.
+This means that all control flow, *including fall throughs* must be made
+explicit in the LLVM IR. If you violate this rule, the verifier will
+emit an error.
+
+Finally, the CodeGen function returns the phi node as the value computed
+by the if/then/else expression. In our example above, this returned
+value will feed into the code for the top-level function, which will
+create the return instruction.
+
+Overall, we now have the ability to execute conditional code in
+Kaleidoscope. With this extension, Kaleidoscope is a fairly complete
+language that can calculate a wide variety of numeric functions. Next up
+we'll add another useful expression that is familiar from non-functional
+languages...
+
+'for' Loop Expression
+=====================
+
+Now that we know how to add basic control flow constructs to the
+language, we have the tools to add more powerful things. Lets add
+something more aggressive, a 'for' expression:
+
+::
+
+     extern putchard(char);
+     def printstar(n)
+       for i = 1, i < n, 1.0 in
+         putchard(42);  # ascii 42 = '*'
+
+     # print 100 '*' characters
+     printstar(100);
+
+This expression defines a new variable ("i" in this case) which iterates
+from a starting value, while the condition ("i < n" in this case) is
+true, incrementing by an optional step value ("1.0" in this case). If
+the step value is omitted, it defaults to 1.0. While the loop is true,
+it executes its body expression. Because we don't have anything better
+to return, we'll just define the loop as always returning 0.0. In the
+future when we have mutable variables, it will get more useful.
+
+As before, lets talk about the changes that we need to Kaleidoscope to
+support this.
+
+Lexer Extensions for the 'for' Loop
+-----------------------------------
+
+The lexer extensions are the same sort of thing as for if/then/else:
+
+.. code-block:: ocaml
+
+      ... in Token.token ...
+      (* control *)
+      | If | Then | Else
+      | For | In
+
+      ... in Lexer.lex_ident...
+          match Buffer.contents buffer with
+          | "def" -> [< 'Token.Def; stream >]
+          | "extern" -> [< 'Token.Extern; stream >]
+          | "if" -> [< 'Token.If; stream >]
+          | "then" -> [< 'Token.Then; stream >]
+          | "else" -> [< 'Token.Else; stream >]
+          | "for" -> [< 'Token.For; stream >]
+          | "in" -> [< 'Token.In; stream >]
+          | id -> [< 'Token.Ident id; stream >]
+
+AST Extensions for the 'for' Loop
+---------------------------------
+
+The AST variant is just as simple. It basically boils down to capturing
+the variable name and the constituent expressions in the node.
+
+.. code-block:: ocaml
+
+    type expr =
+      ...
+      (* variant for for/in. *)
+      | For of string * expr * expr * expr option * expr
+
+Parser Extensions for the 'for' Loop
+------------------------------------
+
+The parser code is also fairly standard. The only interesting thing here
+is handling of the optional step value. The parser code handles it by
+checking to see if the second comma is present. If not, it sets the step
+value to null in the AST node:
+
+.. code-block:: ocaml
+
+    let rec parse_primary = parser
+      ...
+      (* forexpr
+            ::= 'for' identifier '=' expr ',' expr (',' expr)? 'in' expression *)
+      | [< 'Token.For;
+           'Token.Ident id ?? "expected identifier after for";
+           'Token.Kwd '=' ?? "expected '=' after for";
+           stream >] ->
+          begin parser
+            | [<
+                 start=parse_expr;
+                 'Token.Kwd ',' ?? "expected ',' after for";
+                 end_=parse_expr;
+                 stream >] ->
+                let step =
+                  begin parser
+                  | [< 'Token.Kwd ','; step=parse_expr >] -> Some step
+                  | [< >] -> None
+                  end stream
+                in
+                begin parser
+                | [< 'Token.In; body=parse_expr >] ->
+                    Ast.For (id, start, end_, step, body)
+                | [< >] ->
+                    raise (Stream.Error "expected 'in' after for")
+                end stream
+            | [< >] ->
+                raise (Stream.Error "expected '=' after for")
+          end stream
+
+LLVM IR for the 'for' Loop
+--------------------------
+
+Now we get to the good part: the LLVM IR we want to generate for this
+thing. With the simple example above, we get this LLVM IR (note that
+this dump is generated with optimizations disabled for clarity):
+
+.. code-block:: llvm
+
+    declare double @putchard(double)
+
+    define double @printstar(double %n) {
+    entry:
+            ; initial value = 1.0 (inlined into phi)
+      br label %loop
+
+    loop:    ; preds = %loop, %entry
+      %i = phi double [ 1.000000e+00, %entry ], [ %nextvar, %loop ]
+            ; body
+      %calltmp = call double @putchard(double 4.200000e+01)
+            ; increment
+      %nextvar = fadd double %i, 1.000000e+00
+
+            ; termination test
+      %cmptmp = fcmp ult double %i, %n
+      %booltmp = uitofp i1 %cmptmp to double
+      %loopcond = fcmp one double %booltmp, 0.000000e+00
+      br i1 %loopcond, label %loop, label %afterloop
+
+    afterloop:    ; preds = %loop
+            ; loop always returns 0.0
+      ret double 0.000000e+00
+    }
+
+This loop contains all the same constructs we saw before: a phi node,
+several expressions, and some basic blocks. Lets see how this fits
+together.
+
+Code Generation for the 'for' Loop
+----------------------------------
+
+The first part of Codegen is very simple: we just output the start
+expression for the loop value:
+
+.. code-block:: ocaml
+
+    let rec codegen_expr = function
+      ...
+      | Ast.For (var_name, start, end_, step, body) ->
+          (* Emit the start code first, without 'variable' in scope. *)
+          let start_val = codegen_expr start in
+
+With this out of the way, the next step is to set up the LLVM basic
+block for the start of the loop body. In the case above, the whole loop
+body is one block, but remember that the body code itself could consist
+of multiple blocks (e.g. if it contains an if/then/else or a for/in
+expression).
+
+.. code-block:: ocaml
+
+          (* Make the new basic block for the loop header, inserting after current
+           * block. *)
+          let preheader_bb = insertion_block builder in
+          let the_function = block_parent preheader_bb in
+          let loop_bb = append_block context "loop" the_function in
+
+          (* Insert an explicit fall through from the current block to the
+           * loop_bb. *)
+          ignore (build_br loop_bb builder);
+
+This code is similar to what we saw for if/then/else. Because we will
+need it to create the Phi node, we remember the block that falls through
+into the loop. Once we have that, we create the actual block that starts
+the loop and create an unconditional branch for the fall-through between
+the two blocks.
+
+.. code-block:: ocaml
+
+          (* Start insertion in loop_bb. *)
+          position_at_end loop_bb builder;
+
+          (* Start the PHI node with an entry for start. *)
+          let variable = build_phi [(start_val, preheader_bb)] var_name builder in
+
+Now that the "preheader" for the loop is set up, we switch to emitting
+code for the loop body. To begin with, we move the insertion point and
+create the PHI node for the loop induction variable. Since we already
+know the incoming value for the starting value, we add it to the Phi
+node. Note that the Phi will eventually get a second value for the
+backedge, but we can't set it up yet (because it doesn't exist!).
+
+.. code-block:: ocaml
+
+          (* Within the loop, the variable is defined equal to the PHI node. If it
+           * shadows an existing variable, we have to restore it, so save it
+           * now. *)
+          let old_val =
+            try Some (Hashtbl.find named_values var_name) with Not_found -> None
+          in
+          Hashtbl.add named_values var_name variable;
+
+          (* Emit the body of the loop.  This, like any other expr, can change the
+           * current BB.  Note that we ignore the value computed by the body, but
+           * don't allow an error *)
+          ignore (codegen_expr body);
+
+Now the code starts to get more interesting. Our 'for' loop introduces a
+new variable to the symbol table. This means that our symbol table can
+now contain either function arguments or loop variables. To handle this,
+before we codegen the body of the loop, we add the loop variable as the
+current value for its name. Note that it is possible that there is a
+variable of the same name in the outer scope. It would be easy to make
+this an error (emit an error and return null if there is already an
+entry for VarName) but we choose to allow shadowing of variables. In
+order to handle this correctly, we remember the Value that we are
+potentially shadowing in ``old_val`` (which will be None if there is no
+shadowed variable).
+
+Once the loop variable is set into the symbol table, the code
+recursively codegen's the body. This allows the body to use the loop
+variable: any references to it will naturally find it in the symbol
+table.
+
+.. code-block:: ocaml
+
+          (* Emit the step value. *)
+          let step_val =
+            match step with
+            | Some step -> codegen_expr step
+            (* If not specified, use 1.0. *)
+            | None -> const_float double_type 1.0
+          in
+
+          let next_var = build_add variable step_val "nextvar" builder in
+
+Now that the body is emitted, we compute the next value of the iteration
+variable by adding the step value, or 1.0 if it isn't present.
+'``next_var``' will be the value of the loop variable on the next
+iteration of the loop.
+
+.. code-block:: ocaml
+
+          (* Compute the end condition. *)
+          let end_cond = codegen_expr end_ in
+
+          (* Convert condition to a bool by comparing equal to 0.0. *)
+          let zero = const_float double_type 0.0 in
+          let end_cond = build_fcmp Fcmp.One end_cond zero "loopcond" builder in
+
+Finally, we evaluate the exit value of the loop, to determine whether
+the loop should exit. This mirrors the condition evaluation for the
+if/then/else statement.
+
+.. code-block:: ocaml
+
+          (* Create the "after loop" block and insert it. *)
+          let loop_end_bb = insertion_block builder in
+          let after_bb = append_block context "afterloop" the_function in
+
+          (* Insert the conditional branch into the end of loop_end_bb. *)
+          ignore (build_cond_br end_cond loop_bb after_bb builder);
+
+          (* Any new code will be inserted in after_bb. *)
+          position_at_end after_bb builder;
+
+With the code for the body of the loop complete, we just need to finish
+up the control flow for it. This code remembers the end block (for the
+phi node), then creates the block for the loop exit ("afterloop"). Based
+on the value of the exit condition, it creates a conditional branch that
+chooses between executing the loop again and exiting the loop. Any
+future code is emitted in the "afterloop" block, so it sets the
+insertion position to it.
+
+.. code-block:: ocaml
+
+          (* Add a new entry to the PHI node for the backedge. *)
+          add_incoming (next_var, loop_end_bb) variable;
+
+          (* Restore the unshadowed variable. *)
+          begin match old_val with
+          | Some old_val -> Hashtbl.add named_values var_name old_val
+          | None -> ()
+          end;
+
+          (* for expr always returns 0.0. *)
+          const_null double_type
+
+The final code handles various cleanups: now that we have the
+"``next_var``" value, we can add the incoming value to the loop PHI
+node. After that, we remove the loop variable from the symbol table, so
+that it isn't in scope after the for loop. Finally, code generation of
+the for loop always returns 0.0, so that is what we return from
+``Codegen.codegen_expr``.
+
+With this, we conclude the "adding control flow to Kaleidoscope" chapter
+of the tutorial. In this chapter we added two control flow constructs,
+and used them to motivate a couple of aspects of the LLVM IR that are
+important for front-end implementors to know. In the next chapter of our
+saga, we will get a bit crazier and add `user-defined
+operators <OCamlLangImpl6.html>`_ to our poor innocent language.
+
+Full Code Listing
+=================
+
+Here is the complete code listing for our running example, enhanced with
+the if/then/else and for expressions.. To build this example, use:
+
+.. code-block:: bash
+
+    # Compile
+    ocamlbuild toy.byte
+    # Run
+    ./toy.byte
+
+Here is the code:
+
+\_tags:
+    ::
+
+        <{lexer,parser}.ml>: use_camlp4, pp(camlp4of)
+        <*.{byte,native}>: g++, use_llvm, use_llvm_analysis
+        <*.{byte,native}>: use_llvm_executionengine, use_llvm_target
+        <*.{byte,native}>: use_llvm_scalar_opts, use_bindings
+
+myocamlbuild.ml:
+    .. code-block:: ocaml
+
+        open Ocamlbuild_plugin;;
+
+        ocaml_lib ~extern:true "llvm";;
+        ocaml_lib ~extern:true "llvm_analysis";;
+        ocaml_lib ~extern:true "llvm_executionengine";;
+        ocaml_lib ~extern:true "llvm_target";;
+        ocaml_lib ~extern:true "llvm_scalar_opts";;
+
+        flag ["link"; "ocaml"; "g++"] (S[A"-cc"; A"g++"]);;
+        dep ["link"; "ocaml"; "use_bindings"] ["bindings.o"];;
+
+token.ml:
+    .. code-block:: ocaml
+
+        (*===----------------------------------------------------------------------===
+         * Lexer Tokens
+         *===----------------------------------------------------------------------===*)
+
+        (* The lexer returns these 'Kwd' if it is an unknown character, otherwise one of
+         * these others for known things. *)
+        type token =
+          (* commands *)
+          | Def | Extern
+
+          (* primary *)
+          | Ident of string | Number of float
+
+          (* unknown *)
+          | Kwd of char
+
+          (* control *)
+          | If | Then | Else
+          | For | In
+
+lexer.ml:
+    .. code-block:: ocaml
+
+        (*===----------------------------------------------------------------------===
+         * Lexer
+         *===----------------------------------------------------------------------===*)
+
+        let rec lex = parser
+          (* Skip any whitespace. *)
+          | [< ' (' ' | '\n' | '\r' | '\t'); stream >] -> lex stream
+
+          (* identifier: [a-zA-Z][a-zA-Z0-9] *)
+          | [< ' ('A' .. 'Z' | 'a' .. 'z' as c); stream >] ->
+              let buffer = Buffer.create 1 in
+              Buffer.add_char buffer c;
+              lex_ident buffer stream
+
+          (* number: [0-9.]+ *)
+          | [< ' ('0' .. '9' as c); stream >] ->
+              let buffer = Buffer.create 1 in
+              Buffer.add_char buffer c;
+              lex_number buffer stream
+
+          (* Comment until end of line. *)
+          | [< ' ('#'); stream >] ->
+              lex_comment stream
+
+          (* Otherwise, just return the character as its ascii value. *)
+          | [< 'c; stream >] ->
+              [< 'Token.Kwd c; lex stream >]
+
+          (* end of stream. *)
+          | [< >] -> [< >]
+
+        and lex_number buffer = parser
+          | [< ' ('0' .. '9' | '.' as c); stream >] ->
+              Buffer.add_char buffer c;
+              lex_number buffer stream
+          | [< stream=lex >] ->
+              [< 'Token.Number (float_of_string (Buffer.contents buffer)); stream >]
+
+        and lex_ident buffer = parser
+          | [< ' ('A' .. 'Z' | 'a' .. 'z' | '0' .. '9' as c); stream >] ->
+              Buffer.add_char buffer c;
+              lex_ident buffer stream
+          | [< stream=lex >] ->
+              match Buffer.contents buffer with
+              | "def" -> [< 'Token.Def; stream >]
+              | "extern" -> [< 'Token.Extern; stream >]
+              | "if" -> [< 'Token.If; stream >]
+              | "then" -> [< 'Token.Then; stream >]
+              | "else" -> [< 'Token.Else; stream >]
+              | "for" -> [< 'Token.For; stream >]
+              | "in" -> [< 'Token.In; stream >]
+              | id -> [< 'Token.Ident id; stream >]
+
+        and lex_comment = parser
+          | [< ' ('\n'); stream=lex >] -> stream
+          | [< 'c; e=lex_comment >] -> e
+          | [< >] -> [< >]
+
+ast.ml:
+    .. code-block:: ocaml
+
+        (*===----------------------------------------------------------------------===
+         * Abstract Syntax Tree (aka Parse Tree)
+         *===----------------------------------------------------------------------===*)
+
+        (* expr - Base type for all expression nodes. *)
+        type expr =
+          (* variant for numeric literals like "1.0". *)
+          | Number of float
+
+          (* variant for referencing a variable, like "a". *)
+          | Variable of string
+
+          (* variant for a binary operator. *)
+          | Binary of char * expr * expr
+
+          (* variant for function calls. *)
+          | Call of string * expr array
+
+          (* variant for if/then/else. *)
+          | If of expr * expr * expr
+
+          (* variant for for/in. *)
+          | For of string * expr * expr * expr option * expr
+
+        (* proto - This type represents the "prototype" for a function, which captures
+         * its name, and its argument names (thus implicitly the number of arguments the
+         * function takes). *)
+        type proto = Prototype of string * string array
+
+        (* func - This type represents a function definition itself. *)
+        type func = Function of proto * expr
+
+parser.ml:
+    .. code-block:: ocaml
+
+        (*===---------------------------------------------------------------------===
+         * Parser
+         *===---------------------------------------------------------------------===*)
+
+        (* binop_precedence - This holds the precedence for each binary operator that is
+         * defined *)
+        let binop_precedence:(char, int) Hashtbl.t = Hashtbl.create 10
+
+        (* precedence - Get the precedence of the pending binary operator token. *)
+        let precedence c = try Hashtbl.find binop_precedence c with Not_found -> -1
+
+        (* primary
+         *   ::= identifier
+         *   ::= numberexpr
+         *   ::= parenexpr
+         *   ::= ifexpr
+         *   ::= forexpr *)
+        let rec parse_primary = parser
+          (* numberexpr ::= number *)
+          | [< 'Token.Number n >] -> Ast.Number n
+
+          (* parenexpr ::= '(' expression ')' *)
+          | [< 'Token.Kwd '('; e=parse_expr; 'Token.Kwd ')' ?? "expected ')'" >] -> e
+
+          (* identifierexpr
+           *   ::= identifier
+           *   ::= identifier '(' argumentexpr ')' *)
+          | [< 'Token.Ident id; stream >] ->
+              let rec parse_args accumulator = parser
+                | [< e=parse_expr; stream >] ->
+                    begin parser
+                      | [< 'Token.Kwd ','; e=parse_args (e :: accumulator) >] -> e
+                      | [< >] -> e :: accumulator
+                    end stream
+                | [< >] -> accumulator
+              in
+              let rec parse_ident id = parser
+                (* Call. *)
+                | [< 'Token.Kwd '(';
+                     args=parse_args [];
+                     'Token.Kwd ')' ?? "expected ')'">] ->
+                    Ast.Call (id, Array.of_list (List.rev args))
+
+                (* Simple variable ref. *)
+                | [< >] -> Ast.Variable id
+              in
+              parse_ident id stream
+
+          (* ifexpr ::= 'if' expr 'then' expr 'else' expr *)
+          | [< 'Token.If; c=parse_expr;
+               'Token.Then ?? "expected 'then'"; t=parse_expr;
+               'Token.Else ?? "expected 'else'"; e=parse_expr >] ->
+              Ast.If (c, t, e)
+
+          (* forexpr
+                ::= 'for' identifier '=' expr ',' expr (',' expr)? 'in' expression *)
+          | [< 'Token.For;
+               'Token.Ident id ?? "expected identifier after for";
+               'Token.Kwd '=' ?? "expected '=' after for";
+               stream >] ->
+              begin parser
+                | [<
+                     start=parse_expr;
+                     'Token.Kwd ',' ?? "expected ',' after for";
+                     end_=parse_expr;
+                     stream >] ->
+                    let step =
+                      begin parser
+                      | [< 'Token.Kwd ','; step=parse_expr >] -> Some step
+                      | [< >] -> None
+                      end stream
+                    in
+                    begin parser
+                    | [< 'Token.In; body=parse_expr >] ->
+                        Ast.For (id, start, end_, step, body)
+                    | [< >] ->
+                        raise (Stream.Error "expected 'in' after for")
+                    end stream
+                | [< >] ->
+                    raise (Stream.Error "expected '=' after for")
+              end stream
+
+          | [< >] -> raise (Stream.Error "unknown token when expecting an expression.")
+
+        (* binoprhs
+         *   ::= ('+' primary)* *)
+        and parse_bin_rhs expr_prec lhs stream =
+          match Stream.peek stream with
+          (* If this is a binop, find its precedence. *)
+          | Some (Token.Kwd c) when Hashtbl.mem binop_precedence c ->
+              let token_prec = precedence c in
+
+              (* If this is a binop that binds at least as tightly as the current binop,
+               * consume it, otherwise we are done. *)
+              if token_prec < expr_prec then lhs else begin
+                (* Eat the binop. *)
+                Stream.junk stream;
+
+                (* Parse the primary expression after the binary operator. *)
+                let rhs = parse_primary stream in
+
+                (* Okay, we know this is a binop. *)
+                let rhs =
+                  match Stream.peek stream with
+                  | Some (Token.Kwd c2) ->
+                      (* If BinOp binds less tightly with rhs than the operator after
+                       * rhs, let the pending operator take rhs as its lhs. *)
+                      let next_prec = precedence c2 in
+                      if token_prec < next_prec
+                      then parse_bin_rhs (token_prec + 1) rhs stream
+                      else rhs
+                  | _ -> rhs
+                in
+
+                (* Merge lhs/rhs. *)
+                let lhs = Ast.Binary (c, lhs, rhs) in
+                parse_bin_rhs expr_prec lhs stream
+              end
+          | _ -> lhs
+
+        (* expression
+         *   ::= primary binoprhs *)
+        and parse_expr = parser
+          | [< lhs=parse_primary; stream >] -> parse_bin_rhs 0 lhs stream
+
+        (* prototype
+         *   ::= id '(' id* ')' *)
+        let parse_prototype =
+          let rec parse_args accumulator = parser
+            | [< 'Token.Ident id; e=parse_args (id::accumulator) >] -> e
+            | [< >] -> accumulator
+          in
+
+          parser
+          | [< 'Token.Ident id;
+               'Token.Kwd '(' ?? "expected '(' in prototype";
+               args=parse_args [];
+               'Token.Kwd ')' ?? "expected ')' in prototype" >] ->
+              (* success. *)
+              Ast.Prototype (id, Array.of_list (List.rev args))
+
+          | [< >] ->
+              raise (Stream.Error "expected function name in prototype")
+
+        (* definition ::= 'def' prototype expression *)
+        let parse_definition = parser
+          | [< 'Token.Def; p=parse_prototype; e=parse_expr >] ->
+              Ast.Function (p, e)
+
+        (* toplevelexpr ::= expression *)
+        let parse_toplevel = parser
+          | [< e=parse_expr >] ->
+              (* Make an anonymous proto. *)
+              Ast.Function (Ast.Prototype ("", [||]), e)
+
+        (*  external ::= 'extern' prototype *)
+        let parse_extern = parser
+          | [< 'Token.Extern; e=parse_prototype >] -> e
+
+codegen.ml:
+    .. code-block:: ocaml
+
+        (*===----------------------------------------------------------------------===
+         * Code Generation
+         *===----------------------------------------------------------------------===*)
+
+        open Llvm
+
+        exception Error of string
+
+        let context = global_context ()
+        let the_module = create_module context "my cool jit"
+        let builder = builder context
+        let named_values:(string, llvalue) Hashtbl.t = Hashtbl.create 10
+        let double_type = double_type context
+
+        let rec codegen_expr = function
+          | Ast.Number n -> const_float double_type n
+          | Ast.Variable name ->
+              (try Hashtbl.find named_values name with
+                | Not_found -> raise (Error "unknown variable name"))
+          | Ast.Binary (op, lhs, rhs) ->
+              let lhs_val = codegen_expr lhs in
+              let rhs_val = codegen_expr rhs in
+              begin
+                match op with
+                | '+' -> build_add lhs_val rhs_val "addtmp" builder
+                | '-' -> build_sub lhs_val rhs_val "subtmp" builder
+                | '*' -> build_mul lhs_val rhs_val "multmp" builder
+                | '<' ->
+                    (* Convert bool 0/1 to double 0.0 or 1.0 *)
+                    let i = build_fcmp Fcmp.Ult lhs_val rhs_val "cmptmp" builder in
+                    build_uitofp i double_type "booltmp" builder
+                | _ -> raise (Error "invalid binary operator")
+              end
+          | Ast.Call (callee, args) ->
+              (* Look up the name in the module table. *)
+              let callee =
+                match lookup_function callee the_module with
+                | Some callee -> callee
+                | None -> raise (Error "unknown function referenced")
+              in
+              let params = params callee in
+
+              (* If argument mismatch error. *)
+              if Array.length params == Array.length args then () else
+                raise (Error "incorrect # arguments passed");
+              let args = Array.map codegen_expr args in
+              build_call callee args "calltmp" builder
+          | Ast.If (cond, then_, else_) ->
+              let cond = codegen_expr cond in
+
+              (* Convert condition to a bool by comparing equal to 0.0 *)
+              let zero = const_float double_type 0.0 in
+              let cond_val = build_fcmp Fcmp.One cond zero "ifcond" builder in
+
+              (* Grab the first block so that we might later add the conditional branch
+               * to it at the end of the function. *)
+              let start_bb = insertion_block builder in
+              let the_function = block_parent start_bb in
+
+              let then_bb = append_block context "then" the_function in
+
+              (* Emit 'then' value. *)
+              position_at_end then_bb builder;
+              let then_val = codegen_expr then_ in
+
+              (* Codegen of 'then' can change the current block, update then_bb for the
+               * phi. We create a new name because one is used for the phi node, and the
+               * other is used for the conditional branch. *)
+              let new_then_bb = insertion_block builder in
+
+              (* Emit 'else' value. *)
+              let else_bb = append_block context "else" the_function in
+              position_at_end else_bb builder;
+              let else_val = codegen_expr else_ in
+
+              (* Codegen of 'else' can change the current block, update else_bb for the
+               * phi. *)
+              let new_else_bb = insertion_block builder in
+
+              (* Emit merge block. *)
+              let merge_bb = append_block context "ifcont" the_function in
+              position_at_end merge_bb builder;
+              let incoming = [(then_val, new_then_bb); (else_val, new_else_bb)] in
+              let phi = build_phi incoming "iftmp" builder in
+
+              (* Return to the start block to add the conditional branch. *)
+              position_at_end start_bb builder;
+              ignore (build_cond_br cond_val then_bb else_bb builder);
+
+              (* Set a unconditional branch at the end of the 'then' block and the
+               * 'else' block to the 'merge' block. *)
+              position_at_end new_then_bb builder; ignore (build_br merge_bb builder);
+              position_at_end new_else_bb builder; ignore (build_br merge_bb builder);
+
+              (* Finally, set the builder to the end of the merge block. *)
+              position_at_end merge_bb builder;
+
+              phi
+          | Ast.For (var_name, start, end_, step, body) ->
+              (* Emit the start code first, without 'variable' in scope. *)
+              let start_val = codegen_expr start in
+
+              (* Make the new basic block for the loop header, inserting after current
+               * block. *)
+              let preheader_bb = insertion_block builder in
+              let the_function = block_parent preheader_bb in
+              let loop_bb = append_block context "loop" the_function in
+
+              (* Insert an explicit fall through from the current block to the
+               * loop_bb. *)
+              ignore (build_br loop_bb builder);
+
+              (* Start insertion in loop_bb. *)
+              position_at_end loop_bb builder;
+
+              (* Start the PHI node with an entry for start. *)
+              let variable = build_phi [(start_val, preheader_bb)] var_name builder in
+
+              (* Within the loop, the variable is defined equal to the PHI node. If it
+               * shadows an existing variable, we have to restore it, so save it
+               * now. *)
+              let old_val =
+                try Some (Hashtbl.find named_values var_name) with Not_found -> None
+              in
+              Hashtbl.add named_values var_name variable;
+
+              (* Emit the body of the loop.  This, like any other expr, can change the
+               * current BB.  Note that we ignore the value computed by the body, but
+               * don't allow an error *)
+              ignore (codegen_expr body);
+
+              (* Emit the step value. *)
+              let step_val =
+                match step with
+                | Some step -> codegen_expr step
+                (* If not specified, use 1.0. *)
+                | None -> const_float double_type 1.0
+              in
+
+              let next_var = build_add variable step_val "nextvar" builder in
+
+              (* Compute the end condition. *)
+              let end_cond = codegen_expr end_ in
+
+              (* Convert condition to a bool by comparing equal to 0.0. *)
+              let zero = const_float double_type 0.0 in
+              let end_cond = build_fcmp Fcmp.One end_cond zero "loopcond" builder in
+
+              (* Create the "after loop" block and insert it. *)
+              let loop_end_bb = insertion_block builder in
+              let after_bb = append_block context "afterloop" the_function in
+
+              (* Insert the conditional branch into the end of loop_end_bb. *)
+              ignore (build_cond_br end_cond loop_bb after_bb builder);
+
+              (* Any new code will be inserted in after_bb. *)
+              position_at_end after_bb builder;
+
+              (* Add a new entry to the PHI node for the backedge. *)
+              add_incoming (next_var, loop_end_bb) variable;
+
+              (* Restore the unshadowed variable. *)
+              begin match old_val with
+              | Some old_val -> Hashtbl.add named_values var_name old_val
+              | None -> ()
+              end;
+
+              (* for expr always returns 0.0. *)
+              const_null double_type
+
+        let codegen_proto = function
+          | Ast.Prototype (name, args) ->
+              (* Make the function type: double(double,double) etc. *)
+              let doubles = Array.make (Array.length args) double_type in
+              let ft = function_type double_type doubles in
+              let f =
+                match lookup_function name the_module with
+                | None -> declare_function name ft the_module
+
+                (* If 'f' conflicted, there was already something named 'name'. If it
+                 * has a body, don't allow redefinition or reextern. *)
+                | Some f ->
+                    (* If 'f' already has a body, reject this. *)
+                    if block_begin f <> At_end f then
+                      raise (Error "redefinition of function");
+
+                    (* If 'f' took a different number of arguments, reject. *)
+                    if element_type (type_of f) <> ft then
+                      raise (Error "redefinition of function with different # args");
+                    f
+              in
+
+              (* Set names for all arguments. *)
+              Array.iteri (fun i a ->
+                let n = args.(i) in
+                set_value_name n a;
+                Hashtbl.add named_values n a;
+              ) (params f);
+              f
+
+        let codegen_func the_fpm = function
+          | Ast.Function (proto, body) ->
+              Hashtbl.clear named_values;
+              let the_function = codegen_proto proto in
+
+              (* Create a new basic block to start insertion into. *)
+              let bb = append_block context "entry" the_function in
+              position_at_end bb builder;
+
+              try
+                let ret_val = codegen_expr body in
+
+                (* Finish off the function. *)
+                let _ = build_ret ret_val builder in
+
+                (* Validate the generated code, checking for consistency. *)
+                Llvm_analysis.assert_valid_function the_function;
+
+                (* Optimize the function. *)
+                let _ = PassManager.run_function the_function the_fpm in
+
+                the_function
+              with e ->
+                delete_function the_function;
+                raise e
+
+toplevel.ml:
+    .. code-block:: ocaml
+
+        (*===----------------------------------------------------------------------===
+         * Top-Level parsing and JIT Driver
+         *===----------------------------------------------------------------------===*)
+
+        open Llvm
+        open Llvm_executionengine
+
+        (* top ::= definition | external | expression | ';' *)
+        let rec main_loop the_fpm the_execution_engine stream =
+          match Stream.peek stream with
+          | None -> ()
+
+          (* ignore top-level semicolons. *)
+          | Some (Token.Kwd ';') ->
+              Stream.junk stream;
+              main_loop the_fpm the_execution_engine stream
+
+          | Some token ->
+              begin
+                try match token with
+                | Token.Def ->
+                    let e = Parser.parse_definition stream in
+                    print_endline "parsed a function definition.";
+                    dump_value (Codegen.codegen_func the_fpm e);
+                | Token.Extern ->
+                    let e = Parser.parse_extern stream in
+                    print_endline "parsed an extern.";
+                    dump_value (Codegen.codegen_proto e);
+                | _ ->
+                    (* Evaluate a top-level expression into an anonymous function. *)
+                    let e = Parser.parse_toplevel stream in
+                    print_endline "parsed a top-level expr";
+                    let the_function = Codegen.codegen_func the_fpm e in
+                    dump_value the_function;
+
+                    (* JIT the function, returning a function pointer. *)
+                    let result = ExecutionEngine.run_function the_function [||]
+                      the_execution_engine in
+
+                    print_string "Evaluated to ";
+                    print_float (GenericValue.as_float Codegen.double_type result);
+                    print_newline ();
+                with Stream.Error s | Codegen.Error s ->
+                  (* Skip token for error recovery. *)
+                  Stream.junk stream;
+                  print_endline s;
+              end;
+              print_string "ready> "; flush stdout;
+              main_loop the_fpm the_execution_engine stream
+
+toy.ml:
+    .. code-block:: ocaml
+
+        (*===----------------------------------------------------------------------===
+         * Main driver code.
+         *===----------------------------------------------------------------------===*)
+
+        open Llvm
+        open Llvm_executionengine
+        open Llvm_target
+        open Llvm_scalar_opts
+
+        let main () =
+          ignore (initialize_native_target ());
+
+          (* Install standard binary operators.
+           * 1 is the lowest precedence. *)
+          Hashtbl.add Parser.binop_precedence '<' 10;
+          Hashtbl.add Parser.binop_precedence '+' 20;
+          Hashtbl.add Parser.binop_precedence '-' 20;
+          Hashtbl.add Parser.binop_precedence '*' 40;    (* highest. *)
+
+          (* Prime the first token. *)
+          print_string "ready> "; flush stdout;
+          let stream = Lexer.lex (Stream.of_channel stdin) in
+
+          (* Create the JIT. *)
+          let the_execution_engine = ExecutionEngine.create Codegen.the_module in
+          let the_fpm = PassManager.create_function Codegen.the_module in
+
+          (* Set up the optimizer pipeline.  Start with registering info about how the
+           * target lays out data structures. *)
+          DataLayout.add (ExecutionEngine.target_data the_execution_engine) the_fpm;
+
+          (* Do simple "peephole" optimizations and bit-twiddling optzn. *)
+          add_instruction_combination the_fpm;
+
+          (* reassociate expressions. *)
+          add_reassociation the_fpm;
+
+          (* Eliminate Common SubExpressions. *)
+          add_gvn the_fpm;
+
+          (* Simplify the control flow graph (deleting unreachable blocks, etc). *)
+          add_cfg_simplification the_fpm;
+
+          ignore (PassManager.initialize the_fpm);
+
+          (* Run the main "interpreter loop" now. *)
+          Toplevel.main_loop the_fpm the_execution_engine stream;
+
+          (* Print out all the generated code. *)
+          dump_module Codegen.the_module
+        ;;
+
+        main ()
+
+bindings.c
+    .. code-block:: c
+
+        #include <stdio.h>
+
+        /* putchard - putchar that takes a double and returns 0. */
+        extern double putchard(double X) {
+          putchar((char)X);
+          return 0;
+        }
+
+`Next: Extending the language: user-defined
+operators <OCamlLangImpl6.html>`_
+

Added: www-releases/trunk/3.9.1/docs/_sources/tutorial/OCamlLangImpl6.txt
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_sources/tutorial/OCamlLangImpl6.txt?rev=290368&view=auto
==============================================================================
--- www-releases/trunk/3.9.1/docs/_sources/tutorial/OCamlLangImpl6.txt (added)
+++ www-releases/trunk/3.9.1/docs/_sources/tutorial/OCamlLangImpl6.txt Thu Dec 22 14:04:03 2016
@@ -0,0 +1,1441 @@
+============================================================
+Kaleidoscope: Extending the Language: User-defined Operators
+============================================================
+
+.. contents::
+   :local:
+
+Chapter 6 Introduction
+======================
+
+Welcome to Chapter 6 of the "`Implementing a language with
+LLVM <index.html>`_" tutorial. At this point in our tutorial, we now
+have a fully functional language that is fairly minimal, but also
+useful. There is still one big problem with it, however. Our language
+doesn't have many useful operators (like division, logical negation, or
+even any comparisons besides less-than).
+
+This chapter of the tutorial takes a wild digression into adding
+user-defined operators to the simple and beautiful Kaleidoscope
+language. This digression now gives us a simple and ugly language in
+some ways, but also a powerful one at the same time. One of the great
+things about creating your own language is that you get to decide what
+is good or bad. In this tutorial we'll assume that it is okay to use
+this as a way to show some interesting parsing techniques.
+
+At the end of this tutorial, we'll run through an example Kaleidoscope
+application that `renders the Mandelbrot set <#kicking-the-tires>`_. This gives an
+example of what you can build with Kaleidoscope and its feature set.
+
+User-defined Operators: the Idea
+================================
+
+The "operator overloading" that we will add to Kaleidoscope is more
+general than languages like C++. In C++, you are only allowed to
+redefine existing operators: you can't programatically change the
+grammar, introduce new operators, change precedence levels, etc. In this
+chapter, we will add this capability to Kaleidoscope, which will let the
+user round out the set of operators that are supported.
+
+The point of going into user-defined operators in a tutorial like this
+is to show the power and flexibility of using a hand-written parser.
+Thus far, the parser we have been implementing uses recursive descent
+for most parts of the grammar and operator precedence parsing for the
+expressions. See `Chapter 2 <OCamlLangImpl2.html>`_ for details. Without
+using operator precedence parsing, it would be very difficult to allow
+the programmer to introduce new operators into the grammar: the grammar
+is dynamically extensible as the JIT runs.
+
+The two specific features we'll add are programmable unary operators
+(right now, Kaleidoscope has no unary operators at all) as well as
+binary operators. An example of this is:
+
+::
+
+    # Logical unary not.
+    def unary!(v)
+      if v then
+        0
+      else
+        1;
+
+    # Define > with the same precedence as <.
+    def binary> 10 (LHS RHS)
+      RHS < LHS;
+
+    # Binary "logical or", (note that it does not "short circuit")
+    def binary| 5 (LHS RHS)
+      if LHS then
+        1
+      else if RHS then
+        1
+      else
+        0;
+
+    # Define = with slightly lower precedence than relationals.
+    def binary= 9 (LHS RHS)
+      !(LHS < RHS | LHS > RHS);
+
+Many languages aspire to being able to implement their standard runtime
+library in the language itself. In Kaleidoscope, we can implement
+significant parts of the language in the library!
+
+We will break down implementation of these features into two parts:
+implementing support for user-defined binary operators and adding unary
+operators.
+
+User-defined Binary Operators
+=============================
+
+Adding support for user-defined binary operators is pretty simple with
+our current framework. We'll first add support for the unary/binary
+keywords:
+
+.. code-block:: ocaml
+
+    type token =
+      ...
+      (* operators *)
+      | Binary | Unary
+
+    ...
+
+    and lex_ident buffer = parser
+      ...
+          | "for" -> [< 'Token.For; stream >]
+          | "in" -> [< 'Token.In; stream >]
+          | "binary" -> [< 'Token.Binary; stream >]
+          | "unary" -> [< 'Token.Unary; stream >]
+
+This just adds lexer support for the unary and binary keywords, like we
+did in `previous chapters <OCamlLangImpl5.html#lexer-extensions-for-if-then-else>`_. One nice
+thing about our current AST, is that we represent binary operators with
+full generalisation by using their ASCII code as the opcode. For our
+extended operators, we'll use this same representation, so we don't need
+any new AST or parser support.
+
+On the other hand, we have to be able to represent the definitions of
+these new operators, in the "def binary\| 5" part of the function
+definition. In our grammar so far, the "name" for the function
+definition is parsed as the "prototype" production and into the
+``Ast.Prototype`` AST node. To represent our new user-defined operators
+as prototypes, we have to extend the ``Ast.Prototype`` AST node like
+this:
+
+.. code-block:: ocaml
+
+    (* proto - This type represents the "prototype" for a function, which captures
+     * its name, and its argument names (thus implicitly the number of arguments the
+     * function takes). *)
+    type proto =
+      | Prototype of string * string array
+      | BinOpPrototype of string * string array * int
+
+Basically, in addition to knowing a name for the prototype, we now keep
+track of whether it was an operator, and if it was, what precedence
+level the operator is at. The precedence is only used for binary
+operators (as you'll see below, it just doesn't apply for unary
+operators). Now that we have a way to represent the prototype for a
+user-defined operator, we need to parse it:
+
+.. code-block:: ocaml
+
+    (* prototype
+     *   ::= id '(' id* ')'
+     *   ::= binary LETTER number? (id, id)
+     *   ::= unary LETTER number? (id) *)
+    let parse_prototype =
+      let rec parse_args accumulator = parser
+        | [< 'Token.Ident id; e=parse_args (id::accumulator) >] -> e
+        | [< >] -> accumulator
+      in
+      let parse_operator = parser
+        | [< 'Token.Unary >] -> "unary", 1
+        | [< 'Token.Binary >] -> "binary", 2
+      in
+      let parse_binary_precedence = parser
+        | [< 'Token.Number n >] -> int_of_float n
+        | [< >] -> 30
+      in
+      parser
+      | [< 'Token.Ident id;
+           'Token.Kwd '(' ?? "expected '(' in prototype";
+           args=parse_args [];
+           'Token.Kwd ')' ?? "expected ')' in prototype" >] ->
+          (* success. *)
+          Ast.Prototype (id, Array.of_list (List.rev args))
+      | [< (prefix, kind)=parse_operator;
+           'Token.Kwd op ?? "expected an operator";
+           (* Read the precedence if present. *)
+           binary_precedence=parse_binary_precedence;
+           'Token.Kwd '(' ?? "expected '(' in prototype";
+            args=parse_args [];
+           'Token.Kwd ')' ?? "expected ')' in prototype" >] ->
+          let name = prefix ^ (String.make 1 op) in
+          let args = Array.of_list (List.rev args) in
+
+          (* Verify right number of arguments for operator. *)
+          if Array.length args != kind
+          then raise (Stream.Error "invalid number of operands for operator")
+          else
+            if kind == 1 then
+              Ast.Prototype (name, args)
+            else
+              Ast.BinOpPrototype (name, args, binary_precedence)
+      | [< >] ->
+          raise (Stream.Error "expected function name in prototype")
+
+This is all fairly straightforward parsing code, and we have already
+seen a lot of similar code in the past. One interesting part about the
+code above is the couple lines that set up ``name`` for binary
+operators. This builds names like "binary@" for a newly defined "@"
+operator. This then takes advantage of the fact that symbol names in the
+LLVM symbol table are allowed to have any character in them, including
+embedded nul characters.
+
+The next interesting thing to add, is codegen support for these binary
+operators. Given our current structure, this is a simple addition of a
+default case for our existing binary operator node:
+
+.. code-block:: ocaml
+
+    let codegen_expr = function
+      ...
+      | Ast.Binary (op, lhs, rhs) ->
+          let lhs_val = codegen_expr lhs in
+          let rhs_val = codegen_expr rhs in
+          begin
+            match op with
+            | '+' -> build_add lhs_val rhs_val "addtmp" builder
+            | '-' -> build_sub lhs_val rhs_val "subtmp" builder
+            | '*' -> build_mul lhs_val rhs_val "multmp" builder
+            | '<' ->
+                (* Convert bool 0/1 to double 0.0 or 1.0 *)
+                let i = build_fcmp Fcmp.Ult lhs_val rhs_val "cmptmp" builder in
+                build_uitofp i double_type "booltmp" builder
+            | _ ->
+                (* If it wasn't a builtin binary operator, it must be a user defined
+                 * one. Emit a call to it. *)
+                let callee = "binary" ^ (String.make 1 op) in
+                let callee =
+                  match lookup_function callee the_module with
+                  | Some callee -> callee
+                  | None -> raise (Error "binary operator not found!")
+                in
+                build_call callee [|lhs_val; rhs_val|] "binop" builder
+          end
+
+As you can see above, the new code is actually really simple. It just
+does a lookup for the appropriate operator in the symbol table and
+generates a function call to it. Since user-defined operators are just
+built as normal functions (because the "prototype" boils down to a
+function with the right name) everything falls into place.
+
+The final piece of code we are missing, is a bit of top level magic:
+
+.. code-block:: ocaml
+
+    let codegen_func the_fpm = function
+      | Ast.Function (proto, body) ->
+          Hashtbl.clear named_values;
+          let the_function = codegen_proto proto in
+
+          (* If this is an operator, install it. *)
+          begin match proto with
+          | Ast.BinOpPrototype (name, args, prec) ->
+              let op = name.[String.length name - 1] in
+              Hashtbl.add Parser.binop_precedence op prec;
+          | _ -> ()
+          end;
+
+          (* Create a new basic block to start insertion into. *)
+          let bb = append_block context "entry" the_function in
+          position_at_end bb builder;
+          ...
+
+Basically, before codegening a function, if it is a user-defined
+operator, we register it in the precedence table. This allows the binary
+operator parsing logic we already have in place to handle it. Since we
+are working on a fully-general operator precedence parser, this is all
+we need to do to "extend the grammar".
+
+Now we have useful user-defined binary operators. This builds a lot on
+the previous framework we built for other operators. Adding unary
+operators is a bit more challenging, because we don't have any framework
+for it yet - lets see what it takes.
+
+User-defined Unary Operators
+============================
+
+Since we don't currently support unary operators in the Kaleidoscope
+language, we'll need to add everything to support them. Above, we added
+simple support for the 'unary' keyword to the lexer. In addition to
+that, we need an AST node:
+
+.. code-block:: ocaml
+
+    type expr =
+      ...
+      (* variant for a unary operator. *)
+      | Unary of char * expr
+      ...
+
+This AST node is very simple and obvious by now. It directly mirrors the
+binary operator AST node, except that it only has one child. With this,
+we need to add the parsing logic. Parsing a unary operator is pretty
+simple: we'll add a new function to do it:
+
+.. code-block:: ocaml
+
+    (* unary
+     *   ::= primary
+     *   ::= '!' unary *)
+    and parse_unary = parser
+      (* If this is a unary operator, read it. *)
+      | [< 'Token.Kwd op when op != '(' && op != ')'; operand=parse_expr >] ->
+          Ast.Unary (op, operand)
+
+      (* If the current token is not an operator, it must be a primary expr. *)
+      | [< stream >] -> parse_primary stream
+
+The grammar we add is pretty straightforward here. If we see a unary
+operator when parsing a primary operator, we eat the operator as a
+prefix and parse the remaining piece as another unary operator. This
+allows us to handle multiple unary operators (e.g. "!!x"). Note that
+unary operators can't have ambiguous parses like binary operators can,
+so there is no need for precedence information.
+
+The problem with this function, is that we need to call ParseUnary from
+somewhere. To do this, we change previous callers of ParsePrimary to
+call ``parse_unary`` instead:
+
+.. code-block:: ocaml
+
+    (* binoprhs
+     *   ::= ('+' primary)* *)
+    and parse_bin_rhs expr_prec lhs stream =
+            ...
+            (* Parse the unary expression after the binary operator. *)
+            let rhs = parse_unary stream in
+            ...
+
+    ...
+
+    (* expression
+     *   ::= primary binoprhs *)
+    and parse_expr = parser
+      | [< lhs=parse_unary; stream >] -> parse_bin_rhs 0 lhs stream
+
+With these two simple changes, we are now able to parse unary operators
+and build the AST for them. Next up, we need to add parser support for
+prototypes, to parse the unary operator prototype. We extend the binary
+operator code above with:
+
+.. code-block:: ocaml
+
+    (* prototype
+     *   ::= id '(' id* ')'
+     *   ::= binary LETTER number? (id, id)
+     *   ::= unary LETTER number? (id) *)
+    let parse_prototype =
+      let rec parse_args accumulator = parser
+        | [< 'Token.Ident id; e=parse_args (id::accumulator) >] -> e
+        | [< >] -> accumulator
+      in
+      let parse_operator = parser
+        | [< 'Token.Unary >] -> "unary", 1
+        | [< 'Token.Binary >] -> "binary", 2
+      in
+      let parse_binary_precedence = parser
+        | [< 'Token.Number n >] -> int_of_float n
+        | [< >] -> 30
+      in
+      parser
+      | [< 'Token.Ident id;
+           'Token.Kwd '(' ?? "expected '(' in prototype";
+           args=parse_args [];
+           'Token.Kwd ')' ?? "expected ')' in prototype" >] ->
+          (* success. *)
+          Ast.Prototype (id, Array.of_list (List.rev args))
+      | [< (prefix, kind)=parse_operator;
+           'Token.Kwd op ?? "expected an operator";
+           (* Read the precedence if present. *)
+           binary_precedence=parse_binary_precedence;
+           'Token.Kwd '(' ?? "expected '(' in prototype";
+            args=parse_args [];
+           'Token.Kwd ')' ?? "expected ')' in prototype" >] ->
+          let name = prefix ^ (String.make 1 op) in
+          let args = Array.of_list (List.rev args) in
+
+          (* Verify right number of arguments for operator. *)
+          if Array.length args != kind
+          then raise (Stream.Error "invalid number of operands for operator")
+          else
+            if kind == 1 then
+              Ast.Prototype (name, args)
+            else
+              Ast.BinOpPrototype (name, args, binary_precedence)
+      | [< >] ->
+          raise (Stream.Error "expected function name in prototype")
+
+As with binary operators, we name unary operators with a name that
+includes the operator character. This assists us at code generation
+time. Speaking of, the final piece we need to add is codegen support for
+unary operators. It looks like this:
+
+.. code-block:: ocaml
+
+    let rec codegen_expr = function
+      ...
+      | Ast.Unary (op, operand) ->
+          let operand = codegen_expr operand in
+          let callee = "unary" ^ (String.make 1 op) in
+          let callee =
+            match lookup_function callee the_module with
+            | Some callee -> callee
+            | None -> raise (Error "unknown unary operator")
+          in
+          build_call callee [|operand|] "unop" builder
+
+This code is similar to, but simpler than, the code for binary
+operators. It is simpler primarily because it doesn't need to handle any
+predefined operators.
+
+Kicking the Tires
+=================
+
+It is somewhat hard to believe, but with a few simple extensions we've
+covered in the last chapters, we have grown a real-ish language. With
+this, we can do a lot of interesting things, including I/O, math, and a
+bunch of other things. For example, we can now add a nice sequencing
+operator (printd is defined to print out the specified value and a
+newline):
+
+::
+
+    ready> extern printd(x);
+    Read extern: declare double @printd(double)
+    ready> def binary : 1 (x y) 0;  # Low-precedence operator that ignores operands.
+    ..
+    ready> printd(123) : printd(456) : printd(789);
+    123.000000
+    456.000000
+    789.000000
+    Evaluated to 0.000000
+
+We can also define a bunch of other "primitive" operations, such as:
+
+::
+
+    # Logical unary not.
+    def unary!(v)
+      if v then
+        0
+      else
+        1;
+
+    # Unary negate.
+    def unary-(v)
+      0-v;
+
+    # Define > with the same precedence as <.
+    def binary> 10 (LHS RHS)
+      RHS < LHS;
+
+    # Binary logical or, which does not short circuit.
+    def binary| 5 (LHS RHS)
+      if LHS then
+        1
+      else if RHS then
+        1
+      else
+        0;
+
+    # Binary logical and, which does not short circuit.
+    def binary& 6 (LHS RHS)
+      if !LHS then
+        0
+      else
+        !!RHS;
+
+    # Define = with slightly lower precedence than relationals.
+    def binary = 9 (LHS RHS)
+      !(LHS < RHS | LHS > RHS);
+
+Given the previous if/then/else support, we can also define interesting
+functions for I/O. For example, the following prints out a character
+whose "density" reflects the value passed in: the lower the value, the
+denser the character:
+
+::
+
+    ready>
+
+    extern putchard(char)
+    def printdensity(d)
+      if d > 8 then
+        putchard(32)  # ' '
+      else if d > 4 then
+        putchard(46)  # '.'
+      else if d > 2 then
+        putchard(43)  # '+'
+      else
+        putchard(42); # '*'
+    ...
+    ready> printdensity(1): printdensity(2): printdensity(3) :
+              printdensity(4): printdensity(5): printdensity(9): putchard(10);
+    *++..
+    Evaluated to 0.000000
+
+Based on these simple primitive operations, we can start to define more
+interesting things. For example, here's a little function that solves
+for the number of iterations it takes a function in the complex plane to
+converge:
+
+::
+
+    # determine whether the specific location diverges.
+    # Solve for z = z^2 + c in the complex plane.
+    def mandelconverger(real imag iters creal cimag)
+      if iters > 255 | (real*real + imag*imag > 4) then
+        iters
+      else
+        mandelconverger(real*real - imag*imag + creal,
+                        2*real*imag + cimag,
+                        iters+1, creal, cimag);
+
+    # return the number of iterations required for the iteration to escape
+    def mandelconverge(real imag)
+      mandelconverger(real, imag, 0, real, imag);
+
+This "z = z\ :sup:`2`\  + c" function is a beautiful little creature
+that is the basis for computation of the `Mandelbrot
+Set <http://en.wikipedia.org/wiki/Mandelbrot_set>`_. Our
+``mandelconverge`` function returns the number of iterations that it
+takes for a complex orbit to escape, saturating to 255. This is not a
+very useful function by itself, but if you plot its value over a
+two-dimensional plane, you can see the Mandelbrot set. Given that we are
+limited to using putchard here, our amazing graphical output is limited,
+but we can whip together something using the density plotter above:
+
+::
+
+    # compute and plot the mandelbrot set with the specified 2 dimensional range
+    # info.
+    def mandelhelp(xmin xmax xstep   ymin ymax ystep)
+      for y = ymin, y < ymax, ystep in (
+        (for x = xmin, x < xmax, xstep in
+           printdensity(mandelconverge(x,y)))
+        : putchard(10)
+      )
+
+    # mandel - This is a convenient helper function for plotting the mandelbrot set
+    # from the specified position with the specified Magnification.
+    def mandel(realstart imagstart realmag imagmag)
+      mandelhelp(realstart, realstart+realmag*78, realmag,
+                 imagstart, imagstart+imagmag*40, imagmag);
+
+Given this, we can try plotting out the mandelbrot set! Lets try it out:
+
+::
+
+    ready> mandel(-2.3, -1.3, 0.05, 0.07);
+    *******************************+++++++++++*************************************
+    *************************+++++++++++++++++++++++*******************************
+    **********************+++++++++++++++++++++++++++++****************************
+    *******************+++++++++++++++++++++.. ...++++++++*************************
+    *****************++++++++++++++++++++++.... ...+++++++++***********************
+    ***************+++++++++++++++++++++++.....   ...+++++++++*********************
+    **************+++++++++++++++++++++++....     ....+++++++++********************
+    *************++++++++++++++++++++++......      .....++++++++*******************
+    ************+++++++++++++++++++++.......       .......+++++++******************
+    ***********+++++++++++++++++++....                ... .+++++++*****************
+    **********+++++++++++++++++.......                     .+++++++****************
+    *********++++++++++++++...........                    ...+++++++***************
+    ********++++++++++++............                      ...++++++++**************
+    ********++++++++++... ..........                        .++++++++**************
+    *******+++++++++.....                                   .+++++++++*************
+    *******++++++++......                                  ..+++++++++*************
+    *******++++++.......                                   ..+++++++++*************
+    *******+++++......                                     ..+++++++++*************
+    *******.... ....                                      ...+++++++++*************
+    *******.... .                                         ...+++++++++*************
+    *******+++++......                                    ...+++++++++*************
+    *******++++++.......                                   ..+++++++++*************
+    *******++++++++......                                   .+++++++++*************
+    *******+++++++++.....                                  ..+++++++++*************
+    ********++++++++++... ..........                        .++++++++**************
+    ********++++++++++++............                      ...++++++++**************
+    *********++++++++++++++..........                     ...+++++++***************
+    **********++++++++++++++++........                     .+++++++****************
+    **********++++++++++++++++++++....                ... ..+++++++****************
+    ***********++++++++++++++++++++++.......       .......++++++++*****************
+    ************+++++++++++++++++++++++......      ......++++++++******************
+    **************+++++++++++++++++++++++....      ....++++++++********************
+    ***************+++++++++++++++++++++++.....   ...+++++++++*********************
+    *****************++++++++++++++++++++++....  ...++++++++***********************
+    *******************+++++++++++++++++++++......++++++++*************************
+    *********************++++++++++++++++++++++.++++++++***************************
+    *************************+++++++++++++++++++++++*******************************
+    ******************************+++++++++++++************************************
+    *******************************************************************************
+    *******************************************************************************
+    *******************************************************************************
+    Evaluated to 0.000000
+    ready> mandel(-2, -1, 0.02, 0.04);
+    **************************+++++++++++++++++++++++++++++++++++++++++++++++++++++
+    ***********************++++++++++++++++++++++++++++++++++++++++++++++++++++++++
+    *********************+++++++++++++++++++++++++++++++++++++++++++++++++++++++++.
+    *******************+++++++++++++++++++++++++++++++++++++++++++++++++++++++++...
+    *****************+++++++++++++++++++++++++++++++++++++++++++++++++++++++++.....
+    ***************++++++++++++++++++++++++++++++++++++++++++++++++++++++++........
+    **************++++++++++++++++++++++++++++++++++++++++++++++++++++++...........
+    ************+++++++++++++++++++++++++++++++++++++++++++++++++++++..............
+    ***********++++++++++++++++++++++++++++++++++++++++++++++++++........        .
+    **********++++++++++++++++++++++++++++++++++++++++++++++.............
+    ********+++++++++++++++++++++++++++++++++++++++++++..................
+    *******+++++++++++++++++++++++++++++++++++++++.......................
+    ******+++++++++++++++++++++++++++++++++++...........................
+    *****++++++++++++++++++++++++++++++++............................
+    *****++++++++++++++++++++++++++++...............................
+    ****++++++++++++++++++++++++++......   .........................
+    ***++++++++++++++++++++++++.........     ......    ...........
+    ***++++++++++++++++++++++............
+    **+++++++++++++++++++++..............
+    **+++++++++++++++++++................
+    *++++++++++++++++++.................
+    *++++++++++++++++............ ...
+    *++++++++++++++..............
+    *+++....++++................
+    *..........  ...........
+    *
+    *..........  ...........
+    *+++....++++................
+    *++++++++++++++..............
+    *++++++++++++++++............ ...
+    *++++++++++++++++++.................
+    **+++++++++++++++++++................
+    **+++++++++++++++++++++..............
+    ***++++++++++++++++++++++............
+    ***++++++++++++++++++++++++.........     ......    ...........
+    ****++++++++++++++++++++++++++......   .........................
+    *****++++++++++++++++++++++++++++...............................
+    *****++++++++++++++++++++++++++++++++............................
+    ******+++++++++++++++++++++++++++++++++++...........................
+    *******+++++++++++++++++++++++++++++++++++++++.......................
+    ********+++++++++++++++++++++++++++++++++++++++++++..................
+    Evaluated to 0.000000
+    ready> mandel(-0.9, -1.4, 0.02, 0.03);
+    *******************************************************************************
+    *******************************************************************************
+    *******************************************************************************
+    **********+++++++++++++++++++++************************************************
+    *+++++++++++++++++++++++++++++++++++++++***************************************
+    +++++++++++++++++++++++++++++++++++++++++++++**********************************
+    ++++++++++++++++++++++++++++++++++++++++++++++++++*****************************
+    ++++++++++++++++++++++++++++++++++++++++++++++++++++++*************************
+    +++++++++++++++++++++++++++++++++++++++++++++++++++++++++**********************
+    +++++++++++++++++++++++++++++++++.........++++++++++++++++++*******************
+    +++++++++++++++++++++++++++++++....   ......+++++++++++++++++++****************
+    +++++++++++++++++++++++++++++.......  ........+++++++++++++++++++**************
+    ++++++++++++++++++++++++++++........   ........++++++++++++++++++++************
+    +++++++++++++++++++++++++++.........     ..  ...+++++++++++++++++++++**********
+    ++++++++++++++++++++++++++...........        ....++++++++++++++++++++++********
+    ++++++++++++++++++++++++.............       .......++++++++++++++++++++++******
+    +++++++++++++++++++++++.............        ........+++++++++++++++++++++++****
+    ++++++++++++++++++++++...........           ..........++++++++++++++++++++++***
+    ++++++++++++++++++++...........                .........++++++++++++++++++++++*
+    ++++++++++++++++++............                  ...........++++++++++++++++++++
+    ++++++++++++++++...............                 .............++++++++++++++++++
+    ++++++++++++++.................                 ...............++++++++++++++++
+    ++++++++++++..................                  .................++++++++++++++
+    +++++++++..................                      .................+++++++++++++
+    ++++++........        .                               .........  ..++++++++++++
+    ++............                                         ......    ....++++++++++
+    ..............                                                    ...++++++++++
+    ..............                                                    ....+++++++++
+    ..............                                                    .....++++++++
+    .............                                                    ......++++++++
+    ...........                                                     .......++++++++
+    .........                                                       ........+++++++
+    .........                                                       ........+++++++
+    .........                                                           ....+++++++
+    ........                                                             ...+++++++
+    .......                                                              ...+++++++
+                                                                        ....+++++++
+                                                                       .....+++++++
+                                                                        ....+++++++
+                                                                        ....+++++++
+                                                                        ....+++++++
+    Evaluated to 0.000000
+    ready> ^D
+
+At this point, you may be starting to realize that Kaleidoscope is a
+real and powerful language. It may not be self-similar :), but it can be
+used to plot things that are!
+
+With this, we conclude the "adding user-defined operators" chapter of
+the tutorial. We have successfully augmented our language, adding the
+ability to extend the language in the library, and we have shown how
+this can be used to build a simple but interesting end-user application
+in Kaleidoscope. At this point, Kaleidoscope can build a variety of
+applications that are functional and can call functions with
+side-effects, but it can't actually define and mutate a variable itself.
+
+Strikingly, variable mutation is an important feature of some languages,
+and it is not at all obvious how to `add support for mutable
+variables <OCamlLangImpl7.html>`_ without having to add an "SSA
+construction" phase to your front-end. In the next chapter, we will
+describe how you can add variable mutation without building SSA in your
+front-end.
+
+Full Code Listing
+=================
+
+Here is the complete code listing for our running example, enhanced with
+the if/then/else and for expressions.. To build this example, use:
+
+.. code-block:: bash
+
+    # Compile
+    ocamlbuild toy.byte
+    # Run
+    ./toy.byte
+
+Here is the code:
+
+\_tags:
+    ::
+
+        <{lexer,parser}.ml>: use_camlp4, pp(camlp4of)
+        <*.{byte,native}>: g++, use_llvm, use_llvm_analysis
+        <*.{byte,native}>: use_llvm_executionengine, use_llvm_target
+        <*.{byte,native}>: use_llvm_scalar_opts, use_bindings
+
+myocamlbuild.ml:
+    .. code-block:: ocaml
+
+        open Ocamlbuild_plugin;;
+
+        ocaml_lib ~extern:true "llvm";;
+        ocaml_lib ~extern:true "llvm_analysis";;
+        ocaml_lib ~extern:true "llvm_executionengine";;
+        ocaml_lib ~extern:true "llvm_target";;
+        ocaml_lib ~extern:true "llvm_scalar_opts";;
+
+        flag ["link"; "ocaml"; "g++"] (S[A"-cc"; A"g++"; A"-cclib"; A"-rdynamic"]);;
+        dep ["link"; "ocaml"; "use_bindings"] ["bindings.o"];;
+
+token.ml:
+    .. code-block:: ocaml
+
+        (*===----------------------------------------------------------------------===
+         * Lexer Tokens
+         *===----------------------------------------------------------------------===*)
+
+        (* The lexer returns these 'Kwd' if it is an unknown character, otherwise one of
+         * these others for known things. *)
+        type token =
+          (* commands *)
+          | Def | Extern
+
+          (* primary *)
+          | Ident of string | Number of float
+
+          (* unknown *)
+          | Kwd of char
+
+          (* control *)
+          | If | Then | Else
+          | For | In
+
+          (* operators *)
+          | Binary | Unary
+
+lexer.ml:
+    .. code-block:: ocaml
+
+        (*===----------------------------------------------------------------------===
+         * Lexer
+         *===----------------------------------------------------------------------===*)
+
+        let rec lex = parser
+          (* Skip any whitespace. *)
+          | [< ' (' ' | '\n' | '\r' | '\t'); stream >] -> lex stream
+
+          (* identifier: [a-zA-Z][a-zA-Z0-9] *)
+          | [< ' ('A' .. 'Z' | 'a' .. 'z' as c); stream >] ->
+              let buffer = Buffer.create 1 in
+              Buffer.add_char buffer c;
+              lex_ident buffer stream
+
+          (* number: [0-9.]+ *)
+          | [< ' ('0' .. '9' as c); stream >] ->
+              let buffer = Buffer.create 1 in
+              Buffer.add_char buffer c;
+              lex_number buffer stream
+
+          (* Comment until end of line. *)
+          | [< ' ('#'); stream >] ->
+              lex_comment stream
+
+          (* Otherwise, just return the character as its ascii value. *)
+          | [< 'c; stream >] ->
+              [< 'Token.Kwd c; lex stream >]
+
+          (* end of stream. *)
+          | [< >] -> [< >]
+
+        and lex_number buffer = parser
+          | [< ' ('0' .. '9' | '.' as c); stream >] ->
+              Buffer.add_char buffer c;
+              lex_number buffer stream
+          | [< stream=lex >] ->
+              [< 'Token.Number (float_of_string (Buffer.contents buffer)); stream >]
+
+        and lex_ident buffer = parser
+          | [< ' ('A' .. 'Z' | 'a' .. 'z' | '0' .. '9' as c); stream >] ->
+              Buffer.add_char buffer c;
+              lex_ident buffer stream
+          | [< stream=lex >] ->
+              match Buffer.contents buffer with
+              | "def" -> [< 'Token.Def; stream >]
+              | "extern" -> [< 'Token.Extern; stream >]
+              | "if" -> [< 'Token.If; stream >]
+              | "then" -> [< 'Token.Then; stream >]
+              | "else" -> [< 'Token.Else; stream >]
+              | "for" -> [< 'Token.For; stream >]
+              | "in" -> [< 'Token.In; stream >]
+              | "binary" -> [< 'Token.Binary; stream >]
+              | "unary" -> [< 'Token.Unary; stream >]
+              | id -> [< 'Token.Ident id; stream >]
+
+        and lex_comment = parser
+          | [< ' ('\n'); stream=lex >] -> stream
+          | [< 'c; e=lex_comment >] -> e
+          | [< >] -> [< >]
+
+ast.ml:
+    .. code-block:: ocaml
+
+        (*===----------------------------------------------------------------------===
+         * Abstract Syntax Tree (aka Parse Tree)
+         *===----------------------------------------------------------------------===*)
+
+        (* expr - Base type for all expression nodes. *)
+        type expr =
+          (* variant for numeric literals like "1.0". *)
+          | Number of float
+
+          (* variant for referencing a variable, like "a". *)
+          | Variable of string
+
+          (* variant for a unary operator. *)
+          | Unary of char * expr
+
+          (* variant for a binary operator. *)
+          | Binary of char * expr * expr
+
+          (* variant for function calls. *)
+          | Call of string * expr array
+
+          (* variant for if/then/else. *)
+          | If of expr * expr * expr
+
+          (* variant for for/in. *)
+          | For of string * expr * expr * expr option * expr
+
+        (* proto - This type represents the "prototype" for a function, which captures
+         * its name, and its argument names (thus implicitly the number of arguments the
+         * function takes). *)
+        type proto =
+          | Prototype of string * string array
+          | BinOpPrototype of string * string array * int
+
+        (* func - This type represents a function definition itself. *)
+        type func = Function of proto * expr
+
+parser.ml:
+    .. code-block:: ocaml
+
+        (*===---------------------------------------------------------------------===
+         * Parser
+         *===---------------------------------------------------------------------===*)
+
+        (* binop_precedence - This holds the precedence for each binary operator that is
+         * defined *)
+        let binop_precedence:(char, int) Hashtbl.t = Hashtbl.create 10
+
+        (* precedence - Get the precedence of the pending binary operator token. *)
+        let precedence c = try Hashtbl.find binop_precedence c with Not_found -> -1
+
+        (* primary
+         *   ::= identifier
+         *   ::= numberexpr
+         *   ::= parenexpr
+         *   ::= ifexpr
+         *   ::= forexpr *)
+        let rec parse_primary = parser
+          (* numberexpr ::= number *)
+          | [< 'Token.Number n >] -> Ast.Number n
+
+          (* parenexpr ::= '(' expression ')' *)
+          | [< 'Token.Kwd '('; e=parse_expr; 'Token.Kwd ')' ?? "expected ')'" >] -> e
+
+          (* identifierexpr
+           *   ::= identifier
+           *   ::= identifier '(' argumentexpr ')' *)
+          | [< 'Token.Ident id; stream >] ->
+              let rec parse_args accumulator = parser
+                | [< e=parse_expr; stream >] ->
+                    begin parser
+                      | [< 'Token.Kwd ','; e=parse_args (e :: accumulator) >] -> e
+                      | [< >] -> e :: accumulator
+                    end stream
+                | [< >] -> accumulator
+              in
+              let rec parse_ident id = parser
+                (* Call. *)
+                | [< 'Token.Kwd '(';
+                     args=parse_args [];
+                     'Token.Kwd ')' ?? "expected ')'">] ->
+                    Ast.Call (id, Array.of_list (List.rev args))
+
+                (* Simple variable ref. *)
+                | [< >] -> Ast.Variable id
+              in
+              parse_ident id stream
+
+          (* ifexpr ::= 'if' expr 'then' expr 'else' expr *)
+          | [< 'Token.If; c=parse_expr;
+               'Token.Then ?? "expected 'then'"; t=parse_expr;
+               'Token.Else ?? "expected 'else'"; e=parse_expr >] ->
+              Ast.If (c, t, e)
+
+          (* forexpr
+                ::= 'for' identifier '=' expr ',' expr (',' expr)? 'in' expression *)
+          | [< 'Token.For;
+               'Token.Ident id ?? "expected identifier after for";
+               'Token.Kwd '=' ?? "expected '=' after for";
+               stream >] ->
+              begin parser
+                | [<
+                     start=parse_expr;
+                     'Token.Kwd ',' ?? "expected ',' after for";
+                     end_=parse_expr;
+                     stream >] ->
+                    let step =
+                      begin parser
+                      | [< 'Token.Kwd ','; step=parse_expr >] -> Some step
+                      | [< >] -> None
+                      end stream
+                    in
+                    begin parser
+                    | [< 'Token.In; body=parse_expr >] ->
+                        Ast.For (id, start, end_, step, body)
+                    | [< >] ->
+                        raise (Stream.Error "expected 'in' after for")
+                    end stream
+                | [< >] ->
+                    raise (Stream.Error "expected '=' after for")
+              end stream
+
+          | [< >] -> raise (Stream.Error "unknown token when expecting an expression.")
+
+        (* unary
+         *   ::= primary
+         *   ::= '!' unary *)
+        and parse_unary = parser
+          (* If this is a unary operator, read it. *)
+          | [< 'Token.Kwd op when op != '(' && op != ')'; operand=parse_expr >] ->
+              Ast.Unary (op, operand)
+
+          (* If the current token is not an operator, it must be a primary expr. *)
+          | [< stream >] -> parse_primary stream
+
+        (* binoprhs
+         *   ::= ('+' primary)* *)
+        and parse_bin_rhs expr_prec lhs stream =
+          match Stream.peek stream with
+          (* If this is a binop, find its precedence. *)
+          | Some (Token.Kwd c) when Hashtbl.mem binop_precedence c ->
+              let token_prec = precedence c in
+
+              (* If this is a binop that binds at least as tightly as the current binop,
+               * consume it, otherwise we are done. *)
+              if token_prec < expr_prec then lhs else begin
+                (* Eat the binop. *)
+                Stream.junk stream;
+
+                (* Parse the unary expression after the binary operator. *)
+                let rhs = parse_unary stream in
+
+                (* Okay, we know this is a binop. *)
+                let rhs =
+                  match Stream.peek stream with
+                  | Some (Token.Kwd c2) ->
+                      (* If BinOp binds less tightly with rhs than the operator after
+                       * rhs, let the pending operator take rhs as its lhs. *)
+                      let next_prec = precedence c2 in
+                      if token_prec < next_prec
+                      then parse_bin_rhs (token_prec + 1) rhs stream
+                      else rhs
+                  | _ -> rhs
+                in
+
+                (* Merge lhs/rhs. *)
+                let lhs = Ast.Binary (c, lhs, rhs) in
+                parse_bin_rhs expr_prec lhs stream
+              end
+          | _ -> lhs
+
+        (* expression
+         *   ::= primary binoprhs *)
+        and parse_expr = parser
+          | [< lhs=parse_unary; stream >] -> parse_bin_rhs 0 lhs stream
+
+        (* prototype
+         *   ::= id '(' id* ')'
+         *   ::= binary LETTER number? (id, id)
+         *   ::= unary LETTER number? (id) *)
+        let parse_prototype =
+          let rec parse_args accumulator = parser
+            | [< 'Token.Ident id; e=parse_args (id::accumulator) >] -> e
+            | [< >] -> accumulator
+          in
+          let parse_operator = parser
+            | [< 'Token.Unary >] -> "unary", 1
+            | [< 'Token.Binary >] -> "binary", 2
+          in
+          let parse_binary_precedence = parser
+            | [< 'Token.Number n >] -> int_of_float n
+            | [< >] -> 30
+          in
+          parser
+          | [< 'Token.Ident id;
+               'Token.Kwd '(' ?? "expected '(' in prototype";
+               args=parse_args [];
+               'Token.Kwd ')' ?? "expected ')' in prototype" >] ->
+              (* success. *)
+              Ast.Prototype (id, Array.of_list (List.rev args))
+          | [< (prefix, kind)=parse_operator;
+               'Token.Kwd op ?? "expected an operator";
+               (* Read the precedence if present. *)
+               binary_precedence=parse_binary_precedence;
+               'Token.Kwd '(' ?? "expected '(' in prototype";
+                args=parse_args [];
+               'Token.Kwd ')' ?? "expected ')' in prototype" >] ->
+              let name = prefix ^ (String.make 1 op) in
+              let args = Array.of_list (List.rev args) in
+
+              (* Verify right number of arguments for operator. *)
+              if Array.length args != kind
+              then raise (Stream.Error "invalid number of operands for operator")
+              else
+                if kind == 1 then
+                  Ast.Prototype (name, args)
+                else
+                  Ast.BinOpPrototype (name, args, binary_precedence)
+          | [< >] ->
+              raise (Stream.Error "expected function name in prototype")
+
+        (* definition ::= 'def' prototype expression *)
+        let parse_definition = parser
+          | [< 'Token.Def; p=parse_prototype; e=parse_expr >] ->
+              Ast.Function (p, e)
+
+        (* toplevelexpr ::= expression *)
+        let parse_toplevel = parser
+          | [< e=parse_expr >] ->
+              (* Make an anonymous proto. *)
+              Ast.Function (Ast.Prototype ("", [||]), e)
+
+        (*  external ::= 'extern' prototype *)
+        let parse_extern = parser
+          | [< 'Token.Extern; e=parse_prototype >] -> e
+
+codegen.ml:
+    .. code-block:: ocaml
+
+        (*===----------------------------------------------------------------------===
+         * Code Generation
+         *===----------------------------------------------------------------------===*)
+
+        open Llvm
+
+        exception Error of string
+
+        let context = global_context ()
+        let the_module = create_module context "my cool jit"
+        let builder = builder context
+        let named_values:(string, llvalue) Hashtbl.t = Hashtbl.create 10
+        let double_type = double_type context
+
+        let rec codegen_expr = function
+          | Ast.Number n -> const_float double_type n
+          | Ast.Variable name ->
+              (try Hashtbl.find named_values name with
+                | Not_found -> raise (Error "unknown variable name"))
+          | Ast.Unary (op, operand) ->
+              let operand = codegen_expr operand in
+              let callee = "unary" ^ (String.make 1 op) in
+              let callee =
+                match lookup_function callee the_module with
+                | Some callee -> callee
+                | None -> raise (Error "unknown unary operator")
+              in
+              build_call callee [|operand|] "unop" builder
+          | Ast.Binary (op, lhs, rhs) ->
+              let lhs_val = codegen_expr lhs in
+              let rhs_val = codegen_expr rhs in
+              begin
+                match op with
+                | '+' -> build_add lhs_val rhs_val "addtmp" builder
+                | '-' -> build_sub lhs_val rhs_val "subtmp" builder
+                | '*' -> build_mul lhs_val rhs_val "multmp" builder
+                | '<' ->
+                    (* Convert bool 0/1 to double 0.0 or 1.0 *)
+                    let i = build_fcmp Fcmp.Ult lhs_val rhs_val "cmptmp" builder in
+                    build_uitofp i double_type "booltmp" builder
+                | _ ->
+                    (* If it wasn't a builtin binary operator, it must be a user defined
+                     * one. Emit a call to it. *)
+                    let callee = "binary" ^ (String.make 1 op) in
+                    let callee =
+                      match lookup_function callee the_module with
+                      | Some callee -> callee
+                      | None -> raise (Error "binary operator not found!")
+                    in
+                    build_call callee [|lhs_val; rhs_val|] "binop" builder
+              end
+          | Ast.Call (callee, args) ->
+              (* Look up the name in the module table. *)
+              let callee =
+                match lookup_function callee the_module with
+                | Some callee -> callee
+                | None -> raise (Error "unknown function referenced")
+              in
+              let params = params callee in
+
+              (* If argument mismatch error. *)
+              if Array.length params == Array.length args then () else
+                raise (Error "incorrect # arguments passed");
+              let args = Array.map codegen_expr args in
+              build_call callee args "calltmp" builder
+          | Ast.If (cond, then_, else_) ->
+              let cond = codegen_expr cond in
+
+              (* Convert condition to a bool by comparing equal to 0.0 *)
+              let zero = const_float double_type 0.0 in
+              let cond_val = build_fcmp Fcmp.One cond zero "ifcond" builder in
+
+              (* Grab the first block so that we might later add the conditional branch
+               * to it at the end of the function. *)
+              let start_bb = insertion_block builder in
+              let the_function = block_parent start_bb in
+
+              let then_bb = append_block context "then" the_function in
+
+              (* Emit 'then' value. *)
+              position_at_end then_bb builder;
+              let then_val = codegen_expr then_ in
+
+              (* Codegen of 'then' can change the current block, update then_bb for the
+               * phi. We create a new name because one is used for the phi node, and the
+               * other is used for the conditional branch. *)
+              let new_then_bb = insertion_block builder in
+
+              (* Emit 'else' value. *)
+              let else_bb = append_block context "else" the_function in
+              position_at_end else_bb builder;
+              let else_val = codegen_expr else_ in
+
+              (* Codegen of 'else' can change the current block, update else_bb for the
+               * phi. *)
+              let new_else_bb = insertion_block builder in
+
+              (* Emit merge block. *)
+              let merge_bb = append_block context "ifcont" the_function in
+              position_at_end merge_bb builder;
+              let incoming = [(then_val, new_then_bb); (else_val, new_else_bb)] in
+              let phi = build_phi incoming "iftmp" builder in
+
+              (* Return to the start block to add the conditional branch. *)
+              position_at_end start_bb builder;
+              ignore (build_cond_br cond_val then_bb else_bb builder);
+
+              (* Set a unconditional branch at the end of the 'then' block and the
+               * 'else' block to the 'merge' block. *)
+              position_at_end new_then_bb builder; ignore (build_br merge_bb builder);
+              position_at_end new_else_bb builder; ignore (build_br merge_bb builder);
+
+              (* Finally, set the builder to the end of the merge block. *)
+              position_at_end merge_bb builder;
+
+              phi
+          | Ast.For (var_name, start, end_, step, body) ->
+              (* Emit the start code first, without 'variable' in scope. *)
+              let start_val = codegen_expr start in
+
+              (* Make the new basic block for the loop header, inserting after current
+               * block. *)
+              let preheader_bb = insertion_block builder in
+              let the_function = block_parent preheader_bb in
+              let loop_bb = append_block context "loop" the_function in
+
+              (* Insert an explicit fall through from the current block to the
+               * loop_bb. *)
+              ignore (build_br loop_bb builder);
+
+              (* Start insertion in loop_bb. *)
+              position_at_end loop_bb builder;
+
+              (* Start the PHI node with an entry for start. *)
+              let variable = build_phi [(start_val, preheader_bb)] var_name builder in
+
+              (* Within the loop, the variable is defined equal to the PHI node. If it
+               * shadows an existing variable, we have to restore it, so save it
+               * now. *)
+              let old_val =
+                try Some (Hashtbl.find named_values var_name) with Not_found -> None
+              in
+              Hashtbl.add named_values var_name variable;
+
+              (* Emit the body of the loop.  This, like any other expr, can change the
+               * current BB.  Note that we ignore the value computed by the body, but
+               * don't allow an error *)
+              ignore (codegen_expr body);
+
+              (* Emit the step value. *)
+              let step_val =
+                match step with
+                | Some step -> codegen_expr step
+                (* If not specified, use 1.0. *)
+                | None -> const_float double_type 1.0
+              in
+
+              let next_var = build_add variable step_val "nextvar" builder in
+
+              (* Compute the end condition. *)
+              let end_cond = codegen_expr end_ in
+
+              (* Convert condition to a bool by comparing equal to 0.0. *)
+              let zero = const_float double_type 0.0 in
+              let end_cond = build_fcmp Fcmp.One end_cond zero "loopcond" builder in
+
+              (* Create the "after loop" block and insert it. *)
+              let loop_end_bb = insertion_block builder in
+              let after_bb = append_block context "afterloop" the_function in
+
+              (* Insert the conditional branch into the end of loop_end_bb. *)
+              ignore (build_cond_br end_cond loop_bb after_bb builder);
+
+              (* Any new code will be inserted in after_bb. *)
+              position_at_end after_bb builder;
+
+              (* Add a new entry to the PHI node for the backedge. *)
+              add_incoming (next_var, loop_end_bb) variable;
+
+              (* Restore the unshadowed variable. *)
+              begin match old_val with
+              | Some old_val -> Hashtbl.add named_values var_name old_val
+              | None -> ()
+              end;
+
+              (* for expr always returns 0.0. *)
+              const_null double_type
+
+        let codegen_proto = function
+          | Ast.Prototype (name, args) | Ast.BinOpPrototype (name, args, _) ->
+              (* Make the function type: double(double,double) etc. *)
+              let doubles = Array.make (Array.length args) double_type in
+              let ft = function_type double_type doubles in
+              let f =
+                match lookup_function name the_module with
+                | None -> declare_function name ft the_module
+
+                (* If 'f' conflicted, there was already something named 'name'. If it
+                 * has a body, don't allow redefinition or reextern. *)
+                | Some f ->
+                    (* If 'f' already has a body, reject this. *)
+                    if block_begin f <> At_end f then
+                      raise (Error "redefinition of function");
+
+                    (* If 'f' took a different number of arguments, reject. *)
+                    if element_type (type_of f) <> ft then
+                      raise (Error "redefinition of function with different # args");
+                    f
+              in
+
+              (* Set names for all arguments. *)
+              Array.iteri (fun i a ->
+                let n = args.(i) in
+                set_value_name n a;
+                Hashtbl.add named_values n a;
+              ) (params f);
+              f
+
+        let codegen_func the_fpm = function
+          | Ast.Function (proto, body) ->
+              Hashtbl.clear named_values;
+              let the_function = codegen_proto proto in
+
+              (* If this is an operator, install it. *)
+              begin match proto with
+              | Ast.BinOpPrototype (name, args, prec) ->
+                  let op = name.[String.length name - 1] in
+                  Hashtbl.add Parser.binop_precedence op prec;
+              | _ -> ()
+              end;
+
+              (* Create a new basic block to start insertion into. *)
+              let bb = append_block context "entry" the_function in
+              position_at_end bb builder;
+
+              try
+                let ret_val = codegen_expr body in
+
+                (* Finish off the function. *)
+                let _ = build_ret ret_val builder in
+
+                (* Validate the generated code, checking for consistency. *)
+                Llvm_analysis.assert_valid_function the_function;
+
+                (* Optimize the function. *)
+                let _ = PassManager.run_function the_function the_fpm in
+
+                the_function
+              with e ->
+                delete_function the_function;
+                raise e
+
+toplevel.ml:
+    .. code-block:: ocaml
+
+        (*===----------------------------------------------------------------------===
+         * Top-Level parsing and JIT Driver
+         *===----------------------------------------------------------------------===*)
+
+        open Llvm
+        open Llvm_executionengine
+
+        (* top ::= definition | external | expression | ';' *)
+        let rec main_loop the_fpm the_execution_engine stream =
+          match Stream.peek stream with
+          | None -> ()
+
+          (* ignore top-level semicolons. *)
+          | Some (Token.Kwd ';') ->
+              Stream.junk stream;
+              main_loop the_fpm the_execution_engine stream
+
+          | Some token ->
+              begin
+                try match token with
+                | Token.Def ->
+                    let e = Parser.parse_definition stream in
+                    print_endline "parsed a function definition.";
+                    dump_value (Codegen.codegen_func the_fpm e);
+                | Token.Extern ->
+                    let e = Parser.parse_extern stream in
+                    print_endline "parsed an extern.";
+                    dump_value (Codegen.codegen_proto e);
+                | _ ->
+                    (* Evaluate a top-level expression into an anonymous function. *)
+                    let e = Parser.parse_toplevel stream in
+                    print_endline "parsed a top-level expr";
+                    let the_function = Codegen.codegen_func the_fpm e in
+                    dump_value the_function;
+
+                    (* JIT the function, returning a function pointer. *)
+                    let result = ExecutionEngine.run_function the_function [||]
+                      the_execution_engine in
+
+                    print_string "Evaluated to ";
+                    print_float (GenericValue.as_float Codegen.double_type result);
+                    print_newline ();
+                with Stream.Error s | Codegen.Error s ->
+                  (* Skip token for error recovery. *)
+                  Stream.junk stream;
+                  print_endline s;
+              end;
+              print_string "ready> "; flush stdout;
+              main_loop the_fpm the_execution_engine stream
+
+toy.ml:
+    .. code-block:: ocaml
+
+        (*===----------------------------------------------------------------------===
+         * Main driver code.
+         *===----------------------------------------------------------------------===*)
+
+        open Llvm
+        open Llvm_executionengine
+        open Llvm_target
+        open Llvm_scalar_opts
+
+        let main () =
+          ignore (initialize_native_target ());
+
+          (* Install standard binary operators.
+           * 1 is the lowest precedence. *)
+          Hashtbl.add Parser.binop_precedence '<' 10;
+          Hashtbl.add Parser.binop_precedence '+' 20;
+          Hashtbl.add Parser.binop_precedence '-' 20;
+          Hashtbl.add Parser.binop_precedence '*' 40;    (* highest. *)
+
+          (* Prime the first token. *)
+          print_string "ready> "; flush stdout;
+          let stream = Lexer.lex (Stream.of_channel stdin) in
+
+          (* Create the JIT. *)
+          let the_execution_engine = ExecutionEngine.create Codegen.the_module in
+          let the_fpm = PassManager.create_function Codegen.the_module in
+
+          (* Set up the optimizer pipeline.  Start with registering info about how the
+           * target lays out data structures. *)
+          DataLayout.add (ExecutionEngine.target_data the_execution_engine) the_fpm;
+
+          (* Do simple "peephole" optimizations and bit-twiddling optzn. *)
+          add_instruction_combination the_fpm;
+
+          (* reassociate expressions. *)
+          add_reassociation the_fpm;
+
+          (* Eliminate Common SubExpressions. *)
+          add_gvn the_fpm;
+
+          (* Simplify the control flow graph (deleting unreachable blocks, etc). *)
+          add_cfg_simplification the_fpm;
+
+          ignore (PassManager.initialize the_fpm);
+
+          (* Run the main "interpreter loop" now. *)
+          Toplevel.main_loop the_fpm the_execution_engine stream;
+
+          (* Print out all the generated code. *)
+          dump_module Codegen.the_module
+        ;;
+
+        main ()
+
+bindings.c
+    .. code-block:: c
+
+        #include <stdio.h>
+
+        /* putchard - putchar that takes a double and returns 0. */
+        extern double putchard(double X) {
+          putchar((char)X);
+          return 0;
+        }
+
+        /* printd - printf that takes a double prints it as "%f\n", returning 0. */
+        extern double printd(double X) {
+          printf("%f\n", X);
+          return 0;
+        }
+
+`Next: Extending the language: mutable variables / SSA
+construction <OCamlLangImpl7.html>`_
+

Added: www-releases/trunk/3.9.1/docs/_sources/tutorial/OCamlLangImpl7.txt
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_sources/tutorial/OCamlLangImpl7.txt?rev=290368&view=auto
==============================================================================
--- www-releases/trunk/3.9.1/docs/_sources/tutorial/OCamlLangImpl7.txt (added)
+++ www-releases/trunk/3.9.1/docs/_sources/tutorial/OCamlLangImpl7.txt Thu Dec 22 14:04:03 2016
@@ -0,0 +1,1723 @@
+=======================================================
+Kaleidoscope: Extending the Language: Mutable Variables
+=======================================================
+
+.. contents::
+   :local:
+
+Chapter 7 Introduction
+======================
+
+Welcome to Chapter 7 of the "`Implementing a language with
+LLVM <index.html>`_" tutorial. In chapters 1 through 6, we've built a
+very respectable, albeit simple, `functional programming
+language <http://en.wikipedia.org/wiki/Functional_programming>`_. In our
+journey, we learned some parsing techniques, how to build and represent
+an AST, how to build LLVM IR, and how to optimize the resultant code as
+well as JIT compile it.
+
+While Kaleidoscope is interesting as a functional language, the fact
+that it is functional makes it "too easy" to generate LLVM IR for it. In
+particular, a functional language makes it very easy to build LLVM IR
+directly in `SSA
+form <http://en.wikipedia.org/wiki/Static_single_assignment_form>`_.
+Since LLVM requires that the input code be in SSA form, this is a very
+nice property and it is often unclear to newcomers how to generate code
+for an imperative language with mutable variables.
+
+The short (and happy) summary of this chapter is that there is no need
+for your front-end to build SSA form: LLVM provides highly tuned and
+well tested support for this, though the way it works is a bit
+unexpected for some.
+
+Why is this a hard problem?
+===========================
+
+To understand why mutable variables cause complexities in SSA
+construction, consider this extremely simple C example:
+
+.. code-block:: c
+
+    int G, H;
+    int test(_Bool Condition) {
+      int X;
+      if (Condition)
+        X = G;
+      else
+        X = H;
+      return X;
+    }
+
+In this case, we have the variable "X", whose value depends on the path
+executed in the program. Because there are two different possible values
+for X before the return instruction, a PHI node is inserted to merge the
+two values. The LLVM IR that we want for this example looks like this:
+
+.. code-block:: llvm
+
+    @G = weak global i32 0   ; type of @G is i32*
+    @H = weak global i32 0   ; type of @H is i32*
+
+    define i32 @test(i1 %Condition) {
+    entry:
+      br i1 %Condition, label %cond_true, label %cond_false
+
+    cond_true:
+      %X.0 = load i32* @G
+      br label %cond_next
+
+    cond_false:
+      %X.1 = load i32* @H
+      br label %cond_next
+
+    cond_next:
+      %X.2 = phi i32 [ %X.1, %cond_false ], [ %X.0, %cond_true ]
+      ret i32 %X.2
+    }
+
+In this example, the loads from the G and H global variables are
+explicit in the LLVM IR, and they live in the then/else branches of the
+if statement (cond\_true/cond\_false). In order to merge the incoming
+values, the X.2 phi node in the cond\_next block selects the right value
+to use based on where control flow is coming from: if control flow comes
+from the cond\_false block, X.2 gets the value of X.1. Alternatively, if
+control flow comes from cond\_true, it gets the value of X.0. The intent
+of this chapter is not to explain the details of SSA form. For more
+information, see one of the many `online
+references <http://en.wikipedia.org/wiki/Static_single_assignment_form>`_.
+
+The question for this article is "who places the phi nodes when lowering
+assignments to mutable variables?". The issue here is that LLVM
+*requires* that its IR be in SSA form: there is no "non-ssa" mode for
+it. However, SSA construction requires non-trivial algorithms and data
+structures, so it is inconvenient and wasteful for every front-end to
+have to reproduce this logic.
+
+Memory in LLVM
+==============
+
+The 'trick' here is that while LLVM does require all register values to
+be in SSA form, it does not require (or permit) memory objects to be in
+SSA form. In the example above, note that the loads from G and H are
+direct accesses to G and H: they are not renamed or versioned. This
+differs from some other compiler systems, which do try to version memory
+objects. In LLVM, instead of encoding dataflow analysis of memory into
+the LLVM IR, it is handled with `Analysis
+Passes <../WritingAnLLVMPass.html>`_ which are computed on demand.
+
+With this in mind, the high-level idea is that we want to make a stack
+variable (which lives in memory, because it is on the stack) for each
+mutable object in a function. To take advantage of this trick, we need
+to talk about how LLVM represents stack variables.
+
+In LLVM, all memory accesses are explicit with load/store instructions,
+and it is carefully designed not to have (or need) an "address-of"
+operator. Notice how the type of the @G/@H global variables is actually
+"i32\*" even though the variable is defined as "i32". What this means is
+that @G defines *space* for an i32 in the global data area, but its
+*name* actually refers to the address for that space. Stack variables
+work the same way, except that instead of being declared with global
+variable definitions, they are declared with the `LLVM alloca
+instruction <../LangRef.html#alloca-instruction>`_:
+
+.. code-block:: llvm
+
+    define i32 @example() {
+    entry:
+      %X = alloca i32           ; type of %X is i32*.
+      ...
+      %tmp = load i32* %X       ; load the stack value %X from the stack.
+      %tmp2 = add i32 %tmp, 1   ; increment it
+      store i32 %tmp2, i32* %X  ; store it back
+      ...
+
+This code shows an example of how you can declare and manipulate a stack
+variable in the LLVM IR. Stack memory allocated with the alloca
+instruction is fully general: you can pass the address of the stack slot
+to functions, you can store it in other variables, etc. In our example
+above, we could rewrite the example to use the alloca technique to avoid
+using a PHI node:
+
+.. code-block:: llvm
+
+    @G = weak global i32 0   ; type of @G is i32*
+    @H = weak global i32 0   ; type of @H is i32*
+
+    define i32 @test(i1 %Condition) {
+    entry:
+      %X = alloca i32           ; type of %X is i32*.
+      br i1 %Condition, label %cond_true, label %cond_false
+
+    cond_true:
+      %X.0 = load i32* @G
+            store i32 %X.0, i32* %X   ; Update X
+      br label %cond_next
+
+    cond_false:
+      %X.1 = load i32* @H
+            store i32 %X.1, i32* %X   ; Update X
+      br label %cond_next
+
+    cond_next:
+      %X.2 = load i32* %X       ; Read X
+      ret i32 %X.2
+    }
+
+With this, we have discovered a way to handle arbitrary mutable
+variables without the need to create Phi nodes at all:
+
+#. Each mutable variable becomes a stack allocation.
+#. Each read of the variable becomes a load from the stack.
+#. Each update of the variable becomes a store to the stack.
+#. Taking the address of a variable just uses the stack address
+   directly.
+
+While this solution has solved our immediate problem, it introduced
+another one: we have now apparently introduced a lot of stack traffic
+for very simple and common operations, a major performance problem.
+Fortunately for us, the LLVM optimizer has a highly-tuned optimization
+pass named "mem2reg" that handles this case, promoting allocas like this
+into SSA registers, inserting Phi nodes as appropriate. If you run this
+example through the pass, for example, you'll get:
+
+.. code-block:: bash
+
+    $ llvm-as < example.ll | opt -mem2reg | llvm-dis
+    @G = weak global i32 0
+    @H = weak global i32 0
+
+    define i32 @test(i1 %Condition) {
+    entry:
+      br i1 %Condition, label %cond_true, label %cond_false
+
+    cond_true:
+      %X.0 = load i32* @G
+      br label %cond_next
+
+    cond_false:
+      %X.1 = load i32* @H
+      br label %cond_next
+
+    cond_next:
+      %X.01 = phi i32 [ %X.1, %cond_false ], [ %X.0, %cond_true ]
+      ret i32 %X.01
+    }
+
+The mem2reg pass implements the standard "iterated dominance frontier"
+algorithm for constructing SSA form and has a number of optimizations
+that speed up (very common) degenerate cases. The mem2reg optimization
+pass is the answer to dealing with mutable variables, and we highly
+recommend that you depend on it. Note that mem2reg only works on
+variables in certain circumstances:
+
+#. mem2reg is alloca-driven: it looks for allocas and if it can handle
+   them, it promotes them. It does not apply to global variables or heap
+   allocations.
+#. mem2reg only looks for alloca instructions in the entry block of the
+   function. Being in the entry block guarantees that the alloca is only
+   executed once, which makes analysis simpler.
+#. mem2reg only promotes allocas whose uses are direct loads and stores.
+   If the address of the stack object is passed to a function, or if any
+   funny pointer arithmetic is involved, the alloca will not be
+   promoted.
+#. mem2reg only works on allocas of `first
+   class <../LangRef.html#first-class-types>`_ values (such as pointers,
+   scalars and vectors), and only if the array size of the allocation is
+   1 (or missing in the .ll file). mem2reg is not capable of promoting
+   structs or arrays to registers. Note that the "sroa" pass is
+   more powerful and can promote structs, "unions", and arrays in many
+   cases.
+
+All of these properties are easy to satisfy for most imperative
+languages, and we'll illustrate it below with Kaleidoscope. The final
+question you may be asking is: should I bother with this nonsense for my
+front-end? Wouldn't it be better if I just did SSA construction
+directly, avoiding use of the mem2reg optimization pass? In short, we
+strongly recommend that you use this technique for building SSA form,
+unless there is an extremely good reason not to. Using this technique
+is:
+
+-  Proven and well tested: clang uses this technique
+   for local mutable variables. As such, the most common clients of LLVM
+   are using this to handle a bulk of their variables. You can be sure
+   that bugs are found fast and fixed early.
+-  Extremely Fast: mem2reg has a number of special cases that make it
+   fast in common cases as well as fully general. For example, it has
+   fast-paths for variables that are only used in a single block,
+   variables that only have one assignment point, good heuristics to
+   avoid insertion of unneeded phi nodes, etc.
+-  Needed for debug info generation: `Debug information in
+   LLVM <../SourceLevelDebugging.html>`_ relies on having the address of
+   the variable exposed so that debug info can be attached to it. This
+   technique dovetails very naturally with this style of debug info.
+
+If nothing else, this makes it much easier to get your front-end up and
+running, and is very simple to implement. Lets extend Kaleidoscope with
+mutable variables now!
+
+Mutable Variables in Kaleidoscope
+=================================
+
+Now that we know the sort of problem we want to tackle, lets see what
+this looks like in the context of our little Kaleidoscope language.
+We're going to add two features:
+
+#. The ability to mutate variables with the '=' operator.
+#. The ability to define new variables.
+
+While the first item is really what this is about, we only have
+variables for incoming arguments as well as for induction variables, and
+redefining those only goes so far :). Also, the ability to define new
+variables is a useful thing regardless of whether you will be mutating
+them. Here's a motivating example that shows how we could use these:
+
+::
+
+    # Define ':' for sequencing: as a low-precedence operator that ignores operands
+    # and just returns the RHS.
+    def binary : 1 (x y) y;
+
+    # Recursive fib, we could do this before.
+    def fib(x)
+      if (x < 3) then
+        1
+      else
+        fib(x-1)+fib(x-2);
+
+    # Iterative fib.
+    def fibi(x)
+      var a = 1, b = 1, c in
+      (for i = 3, i < x in
+         c = a + b :
+         a = b :
+         b = c) :
+      b;
+
+    # Call it.
+    fibi(10);
+
+In order to mutate variables, we have to change our existing variables
+to use the "alloca trick". Once we have that, we'll add our new
+operator, then extend Kaleidoscope to support new variable definitions.
+
+Adjusting Existing Variables for Mutation
+=========================================
+
+The symbol table in Kaleidoscope is managed at code generation time by
+the '``named_values``' map. This map currently keeps track of the LLVM
+"Value\*" that holds the double value for the named variable. In order
+to support mutation, we need to change this slightly, so that it
+``named_values`` holds the *memory location* of the variable in
+question. Note that this change is a refactoring: it changes the
+structure of the code, but does not (by itself) change the behavior of
+the compiler. All of these changes are isolated in the Kaleidoscope code
+generator.
+
+At this point in Kaleidoscope's development, it only supports variables
+for two things: incoming arguments to functions and the induction
+variable of 'for' loops. For consistency, we'll allow mutation of these
+variables in addition to other user-defined variables. This means that
+these will both need memory locations.
+
+To start our transformation of Kaleidoscope, we'll change the
+``named_values`` map so that it maps to AllocaInst\* instead of Value\*.
+Once we do this, the C++ compiler will tell us what parts of the code we
+need to update:
+
+**Note:** the ocaml bindings currently model both ``Value*``'s and
+``AllocInst*``'s as ``Llvm.llvalue``'s, but this may change in the future
+to be more type safe.
+
+.. code-block:: ocaml
+
+    let named_values:(string, llvalue) Hashtbl.t = Hashtbl.create 10
+
+Also, since we will need to create these alloca's, we'll use a helper
+function that ensures that the allocas are created in the entry block of
+the function:
+
+.. code-block:: ocaml
+
+    (* Create an alloca instruction in the entry block of the function. This
+     * is used for mutable variables etc. *)
+    let create_entry_block_alloca the_function var_name =
+      let builder = builder_at (instr_begin (entry_block the_function)) in
+      build_alloca double_type var_name builder
+
+This funny looking code creates an ``Llvm.llbuilder`` object that is
+pointing at the first instruction of the entry block. It then creates an
+alloca with the expected name and returns it. Because all values in
+Kaleidoscope are doubles, there is no need to pass in a type to use.
+
+With this in place, the first functionality change we want to make is to
+variable references. In our new scheme, variables live on the stack, so
+code generating a reference to them actually needs to produce a load
+from the stack slot:
+
+.. code-block:: ocaml
+
+    let rec codegen_expr = function
+      ...
+      | Ast.Variable name ->
+          let v = try Hashtbl.find named_values name with
+            | Not_found -> raise (Error "unknown variable name")
+          in
+          (* Load the value. *)
+          build_load v name builder
+
+As you can see, this is pretty straightforward. Now we need to update
+the things that define the variables to set up the alloca. We'll start
+with ``codegen_expr Ast.For ...`` (see the `full code listing <#id1>`_
+for the unabridged code):
+
+.. code-block:: ocaml
+
+      | Ast.For (var_name, start, end_, step, body) ->
+          let the_function = block_parent (insertion_block builder) in
+
+          (* Create an alloca for the variable in the entry block. *)
+          let alloca = create_entry_block_alloca the_function var_name in
+
+          (* Emit the start code first, without 'variable' in scope. *)
+          let start_val = codegen_expr start in
+
+          (* Store the value into the alloca. *)
+          ignore(build_store start_val alloca builder);
+
+          ...
+
+          (* Within the loop, the variable is defined equal to the PHI node. If it
+           * shadows an existing variable, we have to restore it, so save it
+           * now. *)
+          let old_val =
+            try Some (Hashtbl.find named_values var_name) with Not_found -> None
+          in
+          Hashtbl.add named_values var_name alloca;
+
+          ...
+
+          (* Compute the end condition. *)
+          let end_cond = codegen_expr end_ in
+
+          (* Reload, increment, and restore the alloca. This handles the case where
+           * the body of the loop mutates the variable. *)
+          let cur_var = build_load alloca var_name builder in
+          let next_var = build_add cur_var step_val "nextvar" builder in
+          ignore(build_store next_var alloca builder);
+          ...
+
+This code is virtually identical to the code `before we allowed mutable
+variables <OCamlLangImpl5.html#code-generation-for-the-for-loop>`_. The big difference is that
+we no longer have to construct a PHI node, and we use load/store to
+access the variable as needed.
+
+To support mutable argument variables, we need to also make allocas for
+them. The code for this is also pretty simple:
+
+.. code-block:: ocaml
+
+    (* Create an alloca for each argument and register the argument in the symbol
+     * table so that references to it will succeed. *)
+    let create_argument_allocas the_function proto =
+      let args = match proto with
+        | Ast.Prototype (_, args) | Ast.BinOpPrototype (_, args, _) -> args
+      in
+      Array.iteri (fun i ai ->
+        let var_name = args.(i) in
+        (* Create an alloca for this variable. *)
+        let alloca = create_entry_block_alloca the_function var_name in
+
+        (* Store the initial value into the alloca. *)
+        ignore(build_store ai alloca builder);
+
+        (* Add arguments to variable symbol table. *)
+        Hashtbl.add named_values var_name alloca;
+      ) (params the_function)
+
+For each argument, we make an alloca, store the input value to the
+function into the alloca, and register the alloca as the memory location
+for the argument. This method gets invoked by ``Codegen.codegen_func``
+right after it sets up the entry block for the function.
+
+The final missing piece is adding the mem2reg pass, which allows us to
+get good codegen once again:
+
+.. code-block:: ocaml
+
+    let main () =
+      ...
+      let the_fpm = PassManager.create_function Codegen.the_module in
+
+      (* Set up the optimizer pipeline.  Start with registering info about how the
+       * target lays out data structures. *)
+      DataLayout.add (ExecutionEngine.target_data the_execution_engine) the_fpm;
+
+      (* Promote allocas to registers. *)
+      add_memory_to_register_promotion the_fpm;
+
+      (* Do simple "peephole" optimizations and bit-twiddling optzn. *)
+      add_instruction_combining the_fpm;
+
+      (* reassociate expressions. *)
+      add_reassociation the_fpm;
+
+It is interesting to see what the code looks like before and after the
+mem2reg optimization runs. For example, this is the before/after code
+for our recursive fib function. Before the optimization:
+
+.. code-block:: llvm
+
+    define double @fib(double %x) {
+    entry:
+      %x1 = alloca double
+      store double %x, double* %x1
+      %x2 = load double* %x1
+      %cmptmp = fcmp ult double %x2, 3.000000e+00
+      %booltmp = uitofp i1 %cmptmp to double
+      %ifcond = fcmp one double %booltmp, 0.000000e+00
+      br i1 %ifcond, label %then, label %else
+
+    then:    ; preds = %entry
+      br label %ifcont
+
+    else:    ; preds = %entry
+      %x3 = load double* %x1
+      %subtmp = fsub double %x3, 1.000000e+00
+      %calltmp = call double @fib(double %subtmp)
+      %x4 = load double* %x1
+      %subtmp5 = fsub double %x4, 2.000000e+00
+      %calltmp6 = call double @fib(double %subtmp5)
+      %addtmp = fadd double %calltmp, %calltmp6
+      br label %ifcont
+
+    ifcont:    ; preds = %else, %then
+      %iftmp = phi double [ 1.000000e+00, %then ], [ %addtmp, %else ]
+      ret double %iftmp
+    }
+
+Here there is only one variable (x, the input argument) but you can
+still see the extremely simple-minded code generation strategy we are
+using. In the entry block, an alloca is created, and the initial input
+value is stored into it. Each reference to the variable does a reload
+from the stack. Also, note that we didn't modify the if/then/else
+expression, so it still inserts a PHI node. While we could make an
+alloca for it, it is actually easier to create a PHI node for it, so we
+still just make the PHI.
+
+Here is the code after the mem2reg pass runs:
+
+.. code-block:: llvm
+
+    define double @fib(double %x) {
+    entry:
+      %cmptmp = fcmp ult double %x, 3.000000e+00
+      %booltmp = uitofp i1 %cmptmp to double
+      %ifcond = fcmp one double %booltmp, 0.000000e+00
+      br i1 %ifcond, label %then, label %else
+
+    then:
+      br label %ifcont
+
+    else:
+      %subtmp = fsub double %x, 1.000000e+00
+      %calltmp = call double @fib(double %subtmp)
+      %subtmp5 = fsub double %x, 2.000000e+00
+      %calltmp6 = call double @fib(double %subtmp5)
+      %addtmp = fadd double %calltmp, %calltmp6
+      br label %ifcont
+
+    ifcont:    ; preds = %else, %then
+      %iftmp = phi double [ 1.000000e+00, %then ], [ %addtmp, %else ]
+      ret double %iftmp
+    }
+
+This is a trivial case for mem2reg, since there are no redefinitions of
+the variable. The point of showing this is to calm your tension about
+inserting such blatent inefficiencies :).
+
+After the rest of the optimizers run, we get:
+
+.. code-block:: llvm
+
+    define double @fib(double %x) {
+    entry:
+      %cmptmp = fcmp ult double %x, 3.000000e+00
+      %booltmp = uitofp i1 %cmptmp to double
+      %ifcond = fcmp ueq double %booltmp, 0.000000e+00
+      br i1 %ifcond, label %else, label %ifcont
+
+    else:
+      %subtmp = fsub double %x, 1.000000e+00
+      %calltmp = call double @fib(double %subtmp)
+      %subtmp5 = fsub double %x, 2.000000e+00
+      %calltmp6 = call double @fib(double %subtmp5)
+      %addtmp = fadd double %calltmp, %calltmp6
+      ret double %addtmp
+
+    ifcont:
+      ret double 1.000000e+00
+    }
+
+Here we see that the simplifycfg pass decided to clone the return
+instruction into the end of the 'else' block. This allowed it to
+eliminate some branches and the PHI node.
+
+Now that all symbol table references are updated to use stack variables,
+we'll add the assignment operator.
+
+New Assignment Operator
+=======================
+
+With our current framework, adding a new assignment operator is really
+simple. We will parse it just like any other binary operator, but handle
+it internally (instead of allowing the user to define it). The first
+step is to set a precedence:
+
+.. code-block:: ocaml
+
+    let main () =
+      (* Install standard binary operators.
+       * 1 is the lowest precedence. *)
+      Hashtbl.add Parser.binop_precedence '=' 2;
+      Hashtbl.add Parser.binop_precedence '<' 10;
+      Hashtbl.add Parser.binop_precedence '+' 20;
+      Hashtbl.add Parser.binop_precedence '-' 20;
+      ...
+
+Now that the parser knows the precedence of the binary operator, it
+takes care of all the parsing and AST generation. We just need to
+implement codegen for the assignment operator. This looks like:
+
+.. code-block:: ocaml
+
+    let rec codegen_expr = function
+          begin match op with
+          | '=' ->
+              (* Special case '=' because we don't want to emit the LHS as an
+               * expression. *)
+              let name =
+                match lhs with
+                | Ast.Variable name -> name
+                | _ -> raise (Error "destination of '=' must be a variable")
+              in
+
+Unlike the rest of the binary operators, our assignment operator doesn't
+follow the "emit LHS, emit RHS, do computation" model. As such, it is
+handled as a special case before the other binary operators are handled.
+The other strange thing is that it requires the LHS to be a variable. It
+is invalid to have "(x+1) = expr" - only things like "x = expr" are
+allowed.
+
+.. code-block:: ocaml
+
+              (* Codegen the rhs. *)
+              let val_ = codegen_expr rhs in
+
+              (* Lookup the name. *)
+              let variable = try Hashtbl.find named_values name with
+              | Not_found -> raise (Error "unknown variable name")
+              in
+              ignore(build_store val_ variable builder);
+              val_
+          | _ ->
+                ...
+
+Once we have the variable, codegen'ing the assignment is
+straightforward: we emit the RHS of the assignment, create a store, and
+return the computed value. Returning a value allows for chained
+assignments like "X = (Y = Z)".
+
+Now that we have an assignment operator, we can mutate loop variables
+and arguments. For example, we can now run code like this:
+
+::
+
+    # Function to print a double.
+    extern printd(x);
+
+    # Define ':' for sequencing: as a low-precedence operator that ignores operands
+    # and just returns the RHS.
+    def binary : 1 (x y) y;
+
+    def test(x)
+      printd(x) :
+      x = 4 :
+      printd(x);
+
+    test(123);
+
+When run, this example prints "123" and then "4", showing that we did
+actually mutate the value! Okay, we have now officially implemented our
+goal: getting this to work requires SSA construction in the general
+case. However, to be really useful, we want the ability to define our
+own local variables, lets add this next!
+
+User-defined Local Variables
+============================
+
+Adding var/in is just like any other other extensions we made to
+Kaleidoscope: we extend the lexer, the parser, the AST and the code
+generator. The first step for adding our new 'var/in' construct is to
+extend the lexer. As before, this is pretty trivial, the code looks like
+this:
+
+.. code-block:: ocaml
+
+    type token =
+      ...
+      (* var definition *)
+      | Var
+
+    ...
+
+    and lex_ident buffer = parser
+          ...
+          | "in" -> [< 'Token.In; stream >]
+          | "binary" -> [< 'Token.Binary; stream >]
+          | "unary" -> [< 'Token.Unary; stream >]
+          | "var" -> [< 'Token.Var; stream >]
+          ...
+
+The next step is to define the AST node that we will construct. For
+var/in, it looks like this:
+
+.. code-block:: ocaml
+
+    type expr =
+      ...
+      (* variant for var/in. *)
+      | Var of (string * expr option) array * expr
+      ...
+
+var/in allows a list of names to be defined all at once, and each name
+can optionally have an initializer value. As such, we capture this
+information in the VarNames vector. Also, var/in has a body, this body
+is allowed to access the variables defined by the var/in.
+
+With this in place, we can define the parser pieces. The first thing we
+do is add it as a primary expression:
+
+.. code-block:: ocaml
+
+    (* primary
+     *   ::= identifier
+     *   ::= numberexpr
+     *   ::= parenexpr
+     *   ::= ifexpr
+     *   ::= forexpr
+     *   ::= varexpr *)
+    let rec parse_primary = parser
+      ...
+      (* varexpr
+       *   ::= 'var' identifier ('=' expression?
+       *             (',' identifier ('=' expression)?)* 'in' expression *)
+      | [< 'Token.Var;
+           (* At least one variable name is required. *)
+           'Token.Ident id ?? "expected identifier after var";
+           init=parse_var_init;
+           var_names=parse_var_names [(id, init)];
+           (* At this point, we have to have 'in'. *)
+           'Token.In ?? "expected 'in' keyword after 'var'";
+           body=parse_expr >] ->
+          Ast.Var (Array.of_list (List.rev var_names), body)
+
+    ...
+
+    and parse_var_init = parser
+      (* read in the optional initializer. *)
+      | [< 'Token.Kwd '='; e=parse_expr >] -> Some e
+      | [< >] -> None
+
+    and parse_var_names accumulator = parser
+      | [< 'Token.Kwd ',';
+           'Token.Ident id ?? "expected identifier list after var";
+           init=parse_var_init;
+           e=parse_var_names ((id, init) :: accumulator) >] -> e
+      | [< >] -> accumulator
+
+Now that we can parse and represent the code, we need to support
+emission of LLVM IR for it. This code starts out with:
+
+.. code-block:: ocaml
+
+    let rec codegen_expr = function
+      ...
+      | Ast.Var (var_names, body)
+          let old_bindings = ref [] in
+
+          let the_function = block_parent (insertion_block builder) in
+
+          (* Register all variables and emit their initializer. *)
+          Array.iter (fun (var_name, init) ->
+
+Basically it loops over all the variables, installing them one at a
+time. For each variable we put into the symbol table, we remember the
+previous value that we replace in OldBindings.
+
+.. code-block:: ocaml
+
+            (* Emit the initializer before adding the variable to scope, this
+             * prevents the initializer from referencing the variable itself, and
+             * permits stuff like this:
+             *   var a = 1 in
+             *     var a = a in ...   # refers to outer 'a'. *)
+            let init_val =
+              match init with
+              | Some init -> codegen_expr init
+              (* If not specified, use 0.0. *)
+              | None -> const_float double_type 0.0
+            in
+
+            let alloca = create_entry_block_alloca the_function var_name in
+            ignore(build_store init_val alloca builder);
+
+            (* Remember the old variable binding so that we can restore the binding
+             * when we unrecurse. *)
+
+            begin
+              try
+                let old_value = Hashtbl.find named_values var_name in
+                old_bindings := (var_name, old_value) :: !old_bindings;
+              with Not_found > ()
+            end;
+
+            (* Remember this binding. *)
+            Hashtbl.add named_values var_name alloca;
+          ) var_names;
+
+There are more comments here than code. The basic idea is that we emit
+the initializer, create the alloca, then update the symbol table to
+point to it. Once all the variables are installed in the symbol table,
+we evaluate the body of the var/in expression:
+
+.. code-block:: ocaml
+
+          (* Codegen the body, now that all vars are in scope. *)
+          let body_val = codegen_expr body in
+
+Finally, before returning, we restore the previous variable bindings:
+
+.. code-block:: ocaml
+
+          (* Pop all our variables from scope. *)
+          List.iter (fun (var_name, old_value) ->
+            Hashtbl.add named_values var_name old_value
+          ) !old_bindings;
+
+          (* Return the body computation. *)
+          body_val
+
+The end result of all of this is that we get properly scoped variable
+definitions, and we even (trivially) allow mutation of them :).
+
+With this, we completed what we set out to do. Our nice iterative fib
+example from the intro compiles and runs just fine. The mem2reg pass
+optimizes all of our stack variables into SSA registers, inserting PHI
+nodes where needed, and our front-end remains simple: no "iterated
+dominance frontier" computation anywhere in sight.
+
+Full Code Listing
+=================
+
+Here is the complete code listing for our running example, enhanced with
+mutable variables and var/in support. To build this example, use:
+
+.. code-block:: bash
+
+    # Compile
+    ocamlbuild toy.byte
+    # Run
+    ./toy.byte
+
+Here is the code:
+
+\_tags:
+    ::
+
+        <{lexer,parser}.ml>: use_camlp4, pp(camlp4of)
+        <*.{byte,native}>: g++, use_llvm, use_llvm_analysis
+        <*.{byte,native}>: use_llvm_executionengine, use_llvm_target
+        <*.{byte,native}>: use_llvm_scalar_opts, use_bindings
+
+myocamlbuild.ml:
+    .. code-block:: ocaml
+
+        open Ocamlbuild_plugin;;
+
+        ocaml_lib ~extern:true "llvm";;
+        ocaml_lib ~extern:true "llvm_analysis";;
+        ocaml_lib ~extern:true "llvm_executionengine";;
+        ocaml_lib ~extern:true "llvm_target";;
+        ocaml_lib ~extern:true "llvm_scalar_opts";;
+
+        flag ["link"; "ocaml"; "g++"] (S[A"-cc"; A"g++"; A"-cclib"; A"-rdynamic"]);;
+        dep ["link"; "ocaml"; "use_bindings"] ["bindings.o"];;
+
+token.ml:
+    .. code-block:: ocaml
+
+        (*===----------------------------------------------------------------------===
+         * Lexer Tokens
+         *===----------------------------------------------------------------------===*)
+
+        (* The lexer returns these 'Kwd' if it is an unknown character, otherwise one of
+         * these others for known things. *)
+        type token =
+          (* commands *)
+          | Def | Extern
+
+          (* primary *)
+          | Ident of string | Number of float
+
+          (* unknown *)
+          | Kwd of char
+
+          (* control *)
+          | If | Then | Else
+          | For | In
+
+          (* operators *)
+          | Binary | Unary
+
+          (* var definition *)
+          | Var
+
+lexer.ml:
+    .. code-block:: ocaml
+
+        (*===----------------------------------------------------------------------===
+         * Lexer
+         *===----------------------------------------------------------------------===*)
+
+        let rec lex = parser
+          (* Skip any whitespace. *)
+          | [< ' (' ' | '\n' | '\r' | '\t'); stream >] -> lex stream
+
+          (* identifier: [a-zA-Z][a-zA-Z0-9] *)
+          | [< ' ('A' .. 'Z' | 'a' .. 'z' as c); stream >] ->
+              let buffer = Buffer.create 1 in
+              Buffer.add_char buffer c;
+              lex_ident buffer stream
+
+          (* number: [0-9.]+ *)
+          | [< ' ('0' .. '9' as c); stream >] ->
+              let buffer = Buffer.create 1 in
+              Buffer.add_char buffer c;
+              lex_number buffer stream
+
+          (* Comment until end of line. *)
+          | [< ' ('#'); stream >] ->
+              lex_comment stream
+
+          (* Otherwise, just return the character as its ascii value. *)
+          | [< 'c; stream >] ->
+              [< 'Token.Kwd c; lex stream >]
+
+          (* end of stream. *)
+          | [< >] -> [< >]
+
+        and lex_number buffer = parser
+          | [< ' ('0' .. '9' | '.' as c); stream >] ->
+              Buffer.add_char buffer c;
+              lex_number buffer stream
+          | [< stream=lex >] ->
+              [< 'Token.Number (float_of_string (Buffer.contents buffer)); stream >]
+
+        and lex_ident buffer = parser
+          | [< ' ('A' .. 'Z' | 'a' .. 'z' | '0' .. '9' as c); stream >] ->
+              Buffer.add_char buffer c;
+              lex_ident buffer stream
+          | [< stream=lex >] ->
+              match Buffer.contents buffer with
+              | "def" -> [< 'Token.Def; stream >]
+              | "extern" -> [< 'Token.Extern; stream >]
+              | "if" -> [< 'Token.If; stream >]
+              | "then" -> [< 'Token.Then; stream >]
+              | "else" -> [< 'Token.Else; stream >]
+              | "for" -> [< 'Token.For; stream >]
+              | "in" -> [< 'Token.In; stream >]
+              | "binary" -> [< 'Token.Binary; stream >]
+              | "unary" -> [< 'Token.Unary; stream >]
+              | "var" -> [< 'Token.Var; stream >]
+              | id -> [< 'Token.Ident id; stream >]
+
+        and lex_comment = parser
+          | [< ' ('\n'); stream=lex >] -> stream
+          | [< 'c; e=lex_comment >] -> e
+          | [< >] -> [< >]
+
+ast.ml:
+    .. code-block:: ocaml
+
+        (*===----------------------------------------------------------------------===
+         * Abstract Syntax Tree (aka Parse Tree)
+         *===----------------------------------------------------------------------===*)
+
+        (* expr - Base type for all expression nodes. *)
+        type expr =
+          (* variant for numeric literals like "1.0". *)
+          | Number of float
+
+          (* variant for referencing a variable, like "a". *)
+          | Variable of string
+
+          (* variant for a unary operator. *)
+          | Unary of char * expr
+
+          (* variant for a binary operator. *)
+          | Binary of char * expr * expr
+
+          (* variant for function calls. *)
+          | Call of string * expr array
+
+          (* variant for if/then/else. *)
+          | If of expr * expr * expr
+
+          (* variant for for/in. *)
+          | For of string * expr * expr * expr option * expr
+
+          (* variant for var/in. *)
+          | Var of (string * expr option) array * expr
+
+        (* proto - This type represents the "prototype" for a function, which captures
+         * its name, and its argument names (thus implicitly the number of arguments the
+         * function takes). *)
+        type proto =
+          | Prototype of string * string array
+          | BinOpPrototype of string * string array * int
+
+        (* func - This type represents a function definition itself. *)
+        type func = Function of proto * expr
+
+parser.ml:
+    .. code-block:: ocaml
+
+        (*===---------------------------------------------------------------------===
+         * Parser
+         *===---------------------------------------------------------------------===*)
+
+        (* binop_precedence - This holds the precedence for each binary operator that is
+         * defined *)
+        let binop_precedence:(char, int) Hashtbl.t = Hashtbl.create 10
+
+        (* precedence - Get the precedence of the pending binary operator token. *)
+        let precedence c = try Hashtbl.find binop_precedence c with Not_found -> -1
+
+        (* primary
+         *   ::= identifier
+         *   ::= numberexpr
+         *   ::= parenexpr
+         *   ::= ifexpr
+         *   ::= forexpr
+         *   ::= varexpr *)
+        let rec parse_primary = parser
+          (* numberexpr ::= number *)
+          | [< 'Token.Number n >] -> Ast.Number n
+
+          (* parenexpr ::= '(' expression ')' *)
+          | [< 'Token.Kwd '('; e=parse_expr; 'Token.Kwd ')' ?? "expected ')'" >] -> e
+
+          (* identifierexpr
+           *   ::= identifier
+           *   ::= identifier '(' argumentexpr ')' *)
+          | [< 'Token.Ident id; stream >] ->
+              let rec parse_args accumulator = parser
+                | [< e=parse_expr; stream >] ->
+                    begin parser
+                      | [< 'Token.Kwd ','; e=parse_args (e :: accumulator) >] -> e
+                      | [< >] -> e :: accumulator
+                    end stream
+                | [< >] -> accumulator
+              in
+              let rec parse_ident id = parser
+                (* Call. *)
+                | [< 'Token.Kwd '(';
+                     args=parse_args [];
+                     'Token.Kwd ')' ?? "expected ')'">] ->
+                    Ast.Call (id, Array.of_list (List.rev args))
+
+                (* Simple variable ref. *)
+                | [< >] -> Ast.Variable id
+              in
+              parse_ident id stream
+
+          (* ifexpr ::= 'if' expr 'then' expr 'else' expr *)
+          | [< 'Token.If; c=parse_expr;
+               'Token.Then ?? "expected 'then'"; t=parse_expr;
+               'Token.Else ?? "expected 'else'"; e=parse_expr >] ->
+              Ast.If (c, t, e)
+
+          (* forexpr
+                ::= 'for' identifier '=' expr ',' expr (',' expr)? 'in' expression *)
+          | [< 'Token.For;
+               'Token.Ident id ?? "expected identifier after for";
+               'Token.Kwd '=' ?? "expected '=' after for";
+               stream >] ->
+              begin parser
+                | [<
+                     start=parse_expr;
+                     'Token.Kwd ',' ?? "expected ',' after for";
+                     end_=parse_expr;
+                     stream >] ->
+                    let step =
+                      begin parser
+                      | [< 'Token.Kwd ','; step=parse_expr >] -> Some step
+                      | [< >] -> None
+                      end stream
+                    in
+                    begin parser
+                    | [< 'Token.In; body=parse_expr >] ->
+                        Ast.For (id, start, end_, step, body)
+                    | [< >] ->
+                        raise (Stream.Error "expected 'in' after for")
+                    end stream
+                | [< >] ->
+                    raise (Stream.Error "expected '=' after for")
+              end stream
+
+          (* varexpr
+           *   ::= 'var' identifier ('=' expression?
+           *             (',' identifier ('=' expression)?)* 'in' expression *)
+          | [< 'Token.Var;
+               (* At least one variable name is required. *)
+               'Token.Ident id ?? "expected identifier after var";
+               init=parse_var_init;
+               var_names=parse_var_names [(id, init)];
+               (* At this point, we have to have 'in'. *)
+               'Token.In ?? "expected 'in' keyword after 'var'";
+               body=parse_expr >] ->
+              Ast.Var (Array.of_list (List.rev var_names), body)
+
+          | [< >] -> raise (Stream.Error "unknown token when expecting an expression.")
+
+        (* unary
+         *   ::= primary
+         *   ::= '!' unary *)
+        and parse_unary = parser
+          (* If this is a unary operator, read it. *)
+          | [< 'Token.Kwd op when op != '(' && op != ')'; operand=parse_expr >] ->
+              Ast.Unary (op, operand)
+
+          (* If the current token is not an operator, it must be a primary expr. *)
+          | [< stream >] -> parse_primary stream
+
+        (* binoprhs
+         *   ::= ('+' primary)* *)
+        and parse_bin_rhs expr_prec lhs stream =
+          match Stream.peek stream with
+          (* If this is a binop, find its precedence. *)
+          | Some (Token.Kwd c) when Hashtbl.mem binop_precedence c ->
+              let token_prec = precedence c in
+
+              (* If this is a binop that binds at least as tightly as the current binop,
+               * consume it, otherwise we are done. *)
+              if token_prec < expr_prec then lhs else begin
+                (* Eat the binop. *)
+                Stream.junk stream;
+
+                (* Parse the primary expression after the binary operator. *)
+                let rhs = parse_unary stream in
+
+                (* Okay, we know this is a binop. *)
+                let rhs =
+                  match Stream.peek stream with
+                  | Some (Token.Kwd c2) ->
+                      (* If BinOp binds less tightly with rhs than the operator after
+                       * rhs, let the pending operator take rhs as its lhs. *)
+                      let next_prec = precedence c2 in
+                      if token_prec < next_prec
+                      then parse_bin_rhs (token_prec + 1) rhs stream
+                      else rhs
+                  | _ -> rhs
+                in
+
+                (* Merge lhs/rhs. *)
+                let lhs = Ast.Binary (c, lhs, rhs) in
+                parse_bin_rhs expr_prec lhs stream
+              end
+          | _ -> lhs
+
+        and parse_var_init = parser
+          (* read in the optional initializer. *)
+          | [< 'Token.Kwd '='; e=parse_expr >] -> Some e
+          | [< >] -> None
+
+        and parse_var_names accumulator = parser
+          | [< 'Token.Kwd ',';
+               'Token.Ident id ?? "expected identifier list after var";
+               init=parse_var_init;
+               e=parse_var_names ((id, init) :: accumulator) >] -> e
+          | [< >] -> accumulator
+
+        (* expression
+         *   ::= primary binoprhs *)
+        and parse_expr = parser
+          | [< lhs=parse_unary; stream >] -> parse_bin_rhs 0 lhs stream
+
+        (* prototype
+         *   ::= id '(' id* ')'
+         *   ::= binary LETTER number? (id, id)
+         *   ::= unary LETTER number? (id) *)
+        let parse_prototype =
+          let rec parse_args accumulator = parser
+            | [< 'Token.Ident id; e=parse_args (id::accumulator) >] -> e
+            | [< >] -> accumulator
+          in
+          let parse_operator = parser
+            | [< 'Token.Unary >] -> "unary", 1
+            | [< 'Token.Binary >] -> "binary", 2
+          in
+          let parse_binary_precedence = parser
+            | [< 'Token.Number n >] -> int_of_float n
+            | [< >] -> 30
+          in
+          parser
+          | [< 'Token.Ident id;
+               'Token.Kwd '(' ?? "expected '(' in prototype";
+               args=parse_args [];
+               'Token.Kwd ')' ?? "expected ')' in prototype" >] ->
+              (* success. *)
+              Ast.Prototype (id, Array.of_list (List.rev args))
+          | [< (prefix, kind)=parse_operator;
+               'Token.Kwd op ?? "expected an operator";
+               (* Read the precedence if present. *)
+               binary_precedence=parse_binary_precedence;
+               'Token.Kwd '(' ?? "expected '(' in prototype";
+                args=parse_args [];
+               'Token.Kwd ')' ?? "expected ')' in prototype" >] ->
+              let name = prefix ^ (String.make 1 op) in
+              let args = Array.of_list (List.rev args) in
+
+              (* Verify right number of arguments for operator. *)
+              if Array.length args != kind
+              then raise (Stream.Error "invalid number of operands for operator")
+              else
+                if kind == 1 then
+                  Ast.Prototype (name, args)
+                else
+                  Ast.BinOpPrototype (name, args, binary_precedence)
+          | [< >] ->
+              raise (Stream.Error "expected function name in prototype")
+
+        (* definition ::= 'def' prototype expression *)
+        let parse_definition = parser
+          | [< 'Token.Def; p=parse_prototype; e=parse_expr >] ->
+              Ast.Function (p, e)
+
+        (* toplevelexpr ::= expression *)
+        let parse_toplevel = parser
+          | [< e=parse_expr >] ->
+              (* Make an anonymous proto. *)
+              Ast.Function (Ast.Prototype ("", [||]), e)
+
+        (*  external ::= 'extern' prototype *)
+        let parse_extern = parser
+          | [< 'Token.Extern; e=parse_prototype >] -> e
+
+codegen.ml:
+    .. code-block:: ocaml
+
+        (*===----------------------------------------------------------------------===
+         * Code Generation
+         *===----------------------------------------------------------------------===*)
+
+        open Llvm
+
+        exception Error of string
+
+        let context = global_context ()
+        let the_module = create_module context "my cool jit"
+        let builder = builder context
+        let named_values:(string, llvalue) Hashtbl.t = Hashtbl.create 10
+        let double_type = double_type context
+
+        (* Create an alloca instruction in the entry block of the function. This
+         * is used for mutable variables etc. *)
+        let create_entry_block_alloca the_function var_name =
+          let builder = builder_at context (instr_begin (entry_block the_function)) in
+          build_alloca double_type var_name builder
+
+        let rec codegen_expr = function
+          | Ast.Number n -> const_float double_type n
+          | Ast.Variable name ->
+              let v = try Hashtbl.find named_values name with
+                | Not_found -> raise (Error "unknown variable name")
+              in
+              (* Load the value. *)
+              build_load v name builder
+          | Ast.Unary (op, operand) ->
+              let operand = codegen_expr operand in
+              let callee = "unary" ^ (String.make 1 op) in
+              let callee =
+                match lookup_function callee the_module with
+                | Some callee -> callee
+                | None -> raise (Error "unknown unary operator")
+              in
+              build_call callee [|operand|] "unop" builder
+          | Ast.Binary (op, lhs, rhs) ->
+              begin match op with
+              | '=' ->
+                  (* Special case '=' because we don't want to emit the LHS as an
+                   * expression. *)
+                  let name =
+                    match lhs with
+                    | Ast.Variable name -> name
+                    | _ -> raise (Error "destination of '=' must be a variable")
+                  in
+
+                  (* Codegen the rhs. *)
+                  let val_ = codegen_expr rhs in
+
+                  (* Lookup the name. *)
+                  let variable = try Hashtbl.find named_values name with
+                  | Not_found -> raise (Error "unknown variable name")
+                  in
+                  ignore(build_store val_ variable builder);
+                  val_
+              | _ ->
+                  let lhs_val = codegen_expr lhs in
+                  let rhs_val = codegen_expr rhs in
+                  begin
+                    match op with
+                    | '+' -> build_add lhs_val rhs_val "addtmp" builder
+                    | '-' -> build_sub lhs_val rhs_val "subtmp" builder
+                    | '*' -> build_mul lhs_val rhs_val "multmp" builder
+                    | '<' ->
+                        (* Convert bool 0/1 to double 0.0 or 1.0 *)
+                        let i = build_fcmp Fcmp.Ult lhs_val rhs_val "cmptmp" builder in
+                        build_uitofp i double_type "booltmp" builder
+                    | _ ->
+                        (* If it wasn't a builtin binary operator, it must be a user defined
+                         * one. Emit a call to it. *)
+                        let callee = "binary" ^ (String.make 1 op) in
+                        let callee =
+                          match lookup_function callee the_module with
+                          | Some callee -> callee
+                          | None -> raise (Error "binary operator not found!")
+                        in
+                        build_call callee [|lhs_val; rhs_val|] "binop" builder
+                  end
+              end
+          | Ast.Call (callee, args) ->
+              (* Look up the name in the module table. *)
+              let callee =
+                match lookup_function callee the_module with
+                | Some callee -> callee
+                | None -> raise (Error "unknown function referenced")
+              in
+              let params = params callee in
+
+              (* If argument mismatch error. *)
+              if Array.length params == Array.length args then () else
+                raise (Error "incorrect # arguments passed");
+              let args = Array.map codegen_expr args in
+              build_call callee args "calltmp" builder
+          | Ast.If (cond, then_, else_) ->
+              let cond = codegen_expr cond in
+
+              (* Convert condition to a bool by comparing equal to 0.0 *)
+              let zero = const_float double_type 0.0 in
+              let cond_val = build_fcmp Fcmp.One cond zero "ifcond" builder in
+
+              (* Grab the first block so that we might later add the conditional branch
+               * to it at the end of the function. *)
+              let start_bb = insertion_block builder in
+              let the_function = block_parent start_bb in
+
+              let then_bb = append_block context "then" the_function in
+
+              (* Emit 'then' value. *)
+              position_at_end then_bb builder;
+              let then_val = codegen_expr then_ in
+
+              (* Codegen of 'then' can change the current block, update then_bb for the
+               * phi. We create a new name because one is used for the phi node, and the
+               * other is used for the conditional branch. *)
+              let new_then_bb = insertion_block builder in
+
+              (* Emit 'else' value. *)
+              let else_bb = append_block context "else" the_function in
+              position_at_end else_bb builder;
+              let else_val = codegen_expr else_ in
+
+              (* Codegen of 'else' can change the current block, update else_bb for the
+               * phi. *)
+              let new_else_bb = insertion_block builder in
+
+              (* Emit merge block. *)
+              let merge_bb = append_block context "ifcont" the_function in
+              position_at_end merge_bb builder;
+              let incoming = [(then_val, new_then_bb); (else_val, new_else_bb)] in
+              let phi = build_phi incoming "iftmp" builder in
+
+              (* Return to the start block to add the conditional branch. *)
+              position_at_end start_bb builder;
+              ignore (build_cond_br cond_val then_bb else_bb builder);
+
+              (* Set a unconditional branch at the end of the 'then' block and the
+               * 'else' block to the 'merge' block. *)
+              position_at_end new_then_bb builder; ignore (build_br merge_bb builder);
+              position_at_end new_else_bb builder; ignore (build_br merge_bb builder);
+
+              (* Finally, set the builder to the end of the merge block. *)
+              position_at_end merge_bb builder;
+
+              phi
+          | Ast.For (var_name, start, end_, step, body) ->
+              (* Output this as:
+               *   var = alloca double
+               *   ...
+               *   start = startexpr
+               *   store start -> var
+               *   goto loop
+               * loop:
+               *   ...
+               *   bodyexpr
+               *   ...
+               * loopend:
+               *   step = stepexpr
+               *   endcond = endexpr
+               *
+               *   curvar = load var
+               *   nextvar = curvar + step
+               *   store nextvar -> var
+               *   br endcond, loop, endloop
+               * outloop: *)
+
+              let the_function = block_parent (insertion_block builder) in
+
+              (* Create an alloca for the variable in the entry block. *)
+              let alloca = create_entry_block_alloca the_function var_name in
+
+              (* Emit the start code first, without 'variable' in scope. *)
+              let start_val = codegen_expr start in
+
+              (* Store the value into the alloca. *)
+              ignore(build_store start_val alloca builder);
+
+              (* Make the new basic block for the loop header, inserting after current
+               * block. *)
+              let loop_bb = append_block context "loop" the_function in
+
+              (* Insert an explicit fall through from the current block to the
+               * loop_bb. *)
+              ignore (build_br loop_bb builder);
+
+              (* Start insertion in loop_bb. *)
+              position_at_end loop_bb builder;
+
+              (* Within the loop, the variable is defined equal to the PHI node. If it
+               * shadows an existing variable, we have to restore it, so save it
+               * now. *)
+              let old_val =
+                try Some (Hashtbl.find named_values var_name) with Not_found -> None
+              in
+              Hashtbl.add named_values var_name alloca;
+
+              (* Emit the body of the loop.  This, like any other expr, can change the
+               * current BB.  Note that we ignore the value computed by the body, but
+               * don't allow an error *)
+              ignore (codegen_expr body);
+
+              (* Emit the step value. *)
+              let step_val =
+                match step with
+                | Some step -> codegen_expr step
+                (* If not specified, use 1.0. *)
+                | None -> const_float double_type 1.0
+              in
+
+              (* Compute the end condition. *)
+              let end_cond = codegen_expr end_ in
+
+              (* Reload, increment, and restore the alloca. This handles the case where
+               * the body of the loop mutates the variable. *)
+              let cur_var = build_load alloca var_name builder in
+              let next_var = build_add cur_var step_val "nextvar" builder in
+              ignore(build_store next_var alloca builder);
+
+              (* Convert condition to a bool by comparing equal to 0.0. *)
+              let zero = const_float double_type 0.0 in
+              let end_cond = build_fcmp Fcmp.One end_cond zero "loopcond" builder in
+
+              (* Create the "after loop" block and insert it. *)
+              let after_bb = append_block context "afterloop" the_function in
+
+              (* Insert the conditional branch into the end of loop_end_bb. *)
+              ignore (build_cond_br end_cond loop_bb after_bb builder);
+
+              (* Any new code will be inserted in after_bb. *)
+              position_at_end after_bb builder;
+
+              (* Restore the unshadowed variable. *)
+              begin match old_val with
+              | Some old_val -> Hashtbl.add named_values var_name old_val
+              | None -> ()
+              end;
+
+              (* for expr always returns 0.0. *)
+              const_null double_type
+          | Ast.Var (var_names, body) ->
+              let old_bindings = ref [] in
+
+              let the_function = block_parent (insertion_block builder) in
+
+              (* Register all variables and emit their initializer. *)
+              Array.iter (fun (var_name, init) ->
+                (* Emit the initializer before adding the variable to scope, this
+                 * prevents the initializer from referencing the variable itself, and
+                 * permits stuff like this:
+                 *   var a = 1 in
+                 *     var a = a in ...   # refers to outer 'a'. *)
+                let init_val =
+                  match init with
+                  | Some init -> codegen_expr init
+                  (* If not specified, use 0.0. *)
+                  | None -> const_float double_type 0.0
+                in
+
+                let alloca = create_entry_block_alloca the_function var_name in
+                ignore(build_store init_val alloca builder);
+
+                (* Remember the old variable binding so that we can restore the binding
+                 * when we unrecurse. *)
+                begin
+                  try
+                    let old_value = Hashtbl.find named_values var_name in
+                    old_bindings := (var_name, old_value) :: !old_bindings;
+                  with Not_found -> ()
+                end;
+
+                (* Remember this binding. *)
+                Hashtbl.add named_values var_name alloca;
+              ) var_names;
+
+              (* Codegen the body, now that all vars are in scope. *)
+              let body_val = codegen_expr body in
+
+              (* Pop all our variables from scope. *)
+              List.iter (fun (var_name, old_value) ->
+                Hashtbl.add named_values var_name old_value
+              ) !old_bindings;
+
+              (* Return the body computation. *)
+              body_val
+
+        let codegen_proto = function
+          | Ast.Prototype (name, args) | Ast.BinOpPrototype (name, args, _) ->
+              (* Make the function type: double(double,double) etc. *)
+              let doubles = Array.make (Array.length args) double_type in
+              let ft = function_type double_type doubles in
+              let f =
+                match lookup_function name the_module with
+                | None -> declare_function name ft the_module
+
+                (* If 'f' conflicted, there was already something named 'name'. If it
+                 * has a body, don't allow redefinition or reextern. *)
+                | Some f ->
+                    (* If 'f' already has a body, reject this. *)
+                    if block_begin f <> At_end f then
+                      raise (Error "redefinition of function");
+
+                    (* If 'f' took a different number of arguments, reject. *)
+                    if element_type (type_of f) <> ft then
+                      raise (Error "redefinition of function with different # args");
+                    f
+              in
+
+              (* Set names for all arguments. *)
+              Array.iteri (fun i a ->
+                let n = args.(i) in
+                set_value_name n a;
+                Hashtbl.add named_values n a;
+              ) (params f);
+              f
+
+        (* Create an alloca for each argument and register the argument in the symbol
+         * table so that references to it will succeed. *)
+        let create_argument_allocas the_function proto =
+          let args = match proto with
+            | Ast.Prototype (_, args) | Ast.BinOpPrototype (_, args, _) -> args
+          in
+          Array.iteri (fun i ai ->
+            let var_name = args.(i) in
+            (* Create an alloca for this variable. *)
+            let alloca = create_entry_block_alloca the_function var_name in
+
+            (* Store the initial value into the alloca. *)
+            ignore(build_store ai alloca builder);
+
+            (* Add arguments to variable symbol table. *)
+            Hashtbl.add named_values var_name alloca;
+          ) (params the_function)
+
+        let codegen_func the_fpm = function
+          | Ast.Function (proto, body) ->
+              Hashtbl.clear named_values;
+              let the_function = codegen_proto proto in
+
+              (* If this is an operator, install it. *)
+              begin match proto with
+              | Ast.BinOpPrototype (name, args, prec) ->
+                  let op = name.[String.length name - 1] in
+                  Hashtbl.add Parser.binop_precedence op prec;
+              | _ -> ()
+              end;
+
+              (* Create a new basic block to start insertion into. *)
+              let bb = append_block context "entry" the_function in
+              position_at_end bb builder;
+
+              try
+                (* Add all arguments to the symbol table and create their allocas. *)
+                create_argument_allocas the_function proto;
+
+                let ret_val = codegen_expr body in
+
+                (* Finish off the function. *)
+                let _ = build_ret ret_val builder in
+
+                (* Validate the generated code, checking for consistency. *)
+                Llvm_analysis.assert_valid_function the_function;
+
+                (* Optimize the function. *)
+                let _ = PassManager.run_function the_function the_fpm in
+
+                the_function
+              with e ->
+                delete_function the_function;
+                raise e
+
+toplevel.ml:
+    .. code-block:: ocaml
+
+        (*===----------------------------------------------------------------------===
+         * Top-Level parsing and JIT Driver
+         *===----------------------------------------------------------------------===*)
+
+        open Llvm
+        open Llvm_executionengine
+
+        (* top ::= definition | external | expression | ';' *)
+        let rec main_loop the_fpm the_execution_engine stream =
+          match Stream.peek stream with
+          | None -> ()
+
+          (* ignore top-level semicolons. *)
+          | Some (Token.Kwd ';') ->
+              Stream.junk stream;
+              main_loop the_fpm the_execution_engine stream
+
+          | Some token ->
+              begin
+                try match token with
+                | Token.Def ->
+                    let e = Parser.parse_definition stream in
+                    print_endline "parsed a function definition.";
+                    dump_value (Codegen.codegen_func the_fpm e);
+                | Token.Extern ->
+                    let e = Parser.parse_extern stream in
+                    print_endline "parsed an extern.";
+                    dump_value (Codegen.codegen_proto e);
+                | _ ->
+                    (* Evaluate a top-level expression into an anonymous function. *)
+                    let e = Parser.parse_toplevel stream in
+                    print_endline "parsed a top-level expr";
+                    let the_function = Codegen.codegen_func the_fpm e in
+                    dump_value the_function;
+
+                    (* JIT the function, returning a function pointer. *)
+                    let result = ExecutionEngine.run_function the_function [||]
+                      the_execution_engine in
+
+                    print_string "Evaluated to ";
+                    print_float (GenericValue.as_float Codegen.double_type result);
+                    print_newline ();
+                with Stream.Error s | Codegen.Error s ->
+                  (* Skip token for error recovery. *)
+                  Stream.junk stream;
+                  print_endline s;
+              end;
+              print_string "ready> "; flush stdout;
+              main_loop the_fpm the_execution_engine stream
+
+toy.ml:
+    .. code-block:: ocaml
+
+        (*===----------------------------------------------------------------------===
+         * Main driver code.
+         *===----------------------------------------------------------------------===*)
+
+        open Llvm
+        open Llvm_executionengine
+        open Llvm_target
+        open Llvm_scalar_opts
+
+        let main () =
+          ignore (initialize_native_target ());
+
+          (* Install standard binary operators.
+           * 1 is the lowest precedence. *)
+          Hashtbl.add Parser.binop_precedence '=' 2;
+          Hashtbl.add Parser.binop_precedence '<' 10;
+          Hashtbl.add Parser.binop_precedence '+' 20;
+          Hashtbl.add Parser.binop_precedence '-' 20;
+          Hashtbl.add Parser.binop_precedence '*' 40;    (* highest. *)
+
+          (* Prime the first token. *)
+          print_string "ready> "; flush stdout;
+          let stream = Lexer.lex (Stream.of_channel stdin) in
+
+          (* Create the JIT. *)
+          let the_execution_engine = ExecutionEngine.create Codegen.the_module in
+          let the_fpm = PassManager.create_function Codegen.the_module in
+
+          (* Set up the optimizer pipeline.  Start with registering info about how the
+           * target lays out data structures. *)
+          DataLayout.add (ExecutionEngine.target_data the_execution_engine) the_fpm;
+
+          (* Promote allocas to registers. *)
+          add_memory_to_register_promotion the_fpm;
+
+          (* Do simple "peephole" optimizations and bit-twiddling optzn. *)
+          add_instruction_combination the_fpm;
+
+          (* reassociate expressions. *)
+          add_reassociation the_fpm;
+
+          (* Eliminate Common SubExpressions. *)
+          add_gvn the_fpm;
+
+          (* Simplify the control flow graph (deleting unreachable blocks, etc). *)
+          add_cfg_simplification the_fpm;
+
+          ignore (PassManager.initialize the_fpm);
+
+          (* Run the main "interpreter loop" now. *)
+          Toplevel.main_loop the_fpm the_execution_engine stream;
+
+          (* Print out all the generated code. *)
+          dump_module Codegen.the_module
+        ;;
+
+        main ()
+
+bindings.c
+    .. code-block:: c
+
+        #include <stdio.h>
+
+        /* putchard - putchar that takes a double and returns 0. */
+        extern double putchard(double X) {
+          putchar((char)X);
+          return 0;
+        }
+
+        /* printd - printf that takes a double prints it as "%f\n", returning 0. */
+        extern double printd(double X) {
+          printf("%f\n", X);
+          return 0;
+        }
+
+`Next: Conclusion and other useful LLVM tidbits <OCamlLangImpl8.html>`_
+

Added: www-releases/trunk/3.9.1/docs/_sources/tutorial/OCamlLangImpl8.txt
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_sources/tutorial/OCamlLangImpl8.txt?rev=290368&view=auto
==============================================================================
--- www-releases/trunk/3.9.1/docs/_sources/tutorial/OCamlLangImpl8.txt (added)
+++ www-releases/trunk/3.9.1/docs/_sources/tutorial/OCamlLangImpl8.txt Thu Dec 22 14:04:03 2016
@@ -0,0 +1,267 @@
+======================================================
+Kaleidoscope: Conclusion and other useful LLVM tidbits
+======================================================
+
+.. contents::
+   :local:
+
+Tutorial Conclusion
+===================
+
+Welcome to the final chapter of the "`Implementing a language with
+LLVM <index.html>`_" tutorial. In the course of this tutorial, we have
+grown our little Kaleidoscope language from being a useless toy, to
+being a semi-interesting (but probably still useless) toy. :)
+
+It is interesting to see how far we've come, and how little code it has
+taken. We built the entire lexer, parser, AST, code generator, and an
+interactive run-loop (with a JIT!) by-hand in under 700 lines of
+(non-comment/non-blank) code.
+
+Our little language supports a couple of interesting features: it
+supports user defined binary and unary operators, it uses JIT
+compilation for immediate evaluation, and it supports a few control flow
+constructs with SSA construction.
+
+Part of the idea of this tutorial was to show you how easy and fun it
+can be to define, build, and play with languages. Building a compiler
+need not be a scary or mystical process! Now that you've seen some of
+the basics, I strongly encourage you to take the code and hack on it.
+For example, try adding:
+
+-  **global variables** - While global variables have questional value
+   in modern software engineering, they are often useful when putting
+   together quick little hacks like the Kaleidoscope compiler itself.
+   Fortunately, our current setup makes it very easy to add global
+   variables: just have value lookup check to see if an unresolved
+   variable is in the global variable symbol table before rejecting it.
+   To create a new global variable, make an instance of the LLVM
+   ``GlobalVariable`` class.
+-  **typed variables** - Kaleidoscope currently only supports variables
+   of type double. This gives the language a very nice elegance, because
+   only supporting one type means that you never have to specify types.
+   Different languages have different ways of handling this. The easiest
+   way is to require the user to specify types for every variable
+   definition, and record the type of the variable in the symbol table
+   along with its Value\*.
+-  **arrays, structs, vectors, etc** - Once you add types, you can start
+   extending the type system in all sorts of interesting ways. Simple
+   arrays are very easy and are quite useful for many different
+   applications. Adding them is mostly an exercise in learning how the
+   LLVM `getelementptr <../LangRef.html#getelementptr-instruction>`_ instruction
+   works: it is so nifty/unconventional, it `has its own
+   FAQ <../GetElementPtr.html>`_! If you add support for recursive types
+   (e.g. linked lists), make sure to read the `section in the LLVM
+   Programmer's Manual <../ProgrammersManual.html#TypeResolve>`_ that
+   describes how to construct them.
+-  **standard runtime** - Our current language allows the user to access
+   arbitrary external functions, and we use it for things like "printd"
+   and "putchard". As you extend the language to add higher-level
+   constructs, often these constructs make the most sense if they are
+   lowered to calls into a language-supplied runtime. For example, if
+   you add hash tables to the language, it would probably make sense to
+   add the routines to a runtime, instead of inlining them all the way.
+-  **memory management** - Currently we can only access the stack in
+   Kaleidoscope. It would also be useful to be able to allocate heap
+   memory, either with calls to the standard libc malloc/free interface
+   or with a garbage collector. If you would like to use garbage
+   collection, note that LLVM fully supports `Accurate Garbage
+   Collection <../GarbageCollection.html>`_ including algorithms that
+   move objects and need to scan/update the stack.
+-  **debugger support** - LLVM supports generation of `DWARF Debug
+   info <../SourceLevelDebugging.html>`_ which is understood by common
+   debuggers like GDB. Adding support for debug info is fairly
+   straightforward. The best way to understand it is to compile some
+   C/C++ code with "``clang -g -O0``" and taking a look at what it
+   produces.
+-  **exception handling support** - LLVM supports generation of `zero
+   cost exceptions <../ExceptionHandling.html>`_ which interoperate with
+   code compiled in other languages. You could also generate code by
+   implicitly making every function return an error value and checking
+   it. You could also make explicit use of setjmp/longjmp. There are
+   many different ways to go here.
+-  **object orientation, generics, database access, complex numbers,
+   geometric programming, ...** - Really, there is no end of crazy
+   features that you can add to the language.
+-  **unusual domains** - We've been talking about applying LLVM to a
+   domain that many people are interested in: building a compiler for a
+   specific language. However, there are many other domains that can use
+   compiler technology that are not typically considered. For example,
+   LLVM has been used to implement OpenGL graphics acceleration,
+   translate C++ code to ActionScript, and many other cute and clever
+   things. Maybe you will be the first to JIT compile a regular
+   expression interpreter into native code with LLVM?
+
+Have fun - try doing something crazy and unusual. Building a language
+like everyone else always has, is much less fun than trying something a
+little crazy or off the wall and seeing how it turns out. If you get
+stuck or want to talk about it, feel free to email the `llvm-dev mailing
+list <http://lists.llvm.org/mailman/listinfo/llvm-dev>`_: it has lots
+of people who are interested in languages and are often willing to help
+out.
+
+Before we end this tutorial, I want to talk about some "tips and tricks"
+for generating LLVM IR. These are some of the more subtle things that
+may not be obvious, but are very useful if you want to take advantage of
+LLVM's capabilities.
+
+Properties of the LLVM IR
+=========================
+
+We have a couple common questions about code in the LLVM IR form - lets
+just get these out of the way right now, shall we?
+
+Target Independence
+-------------------
+
+Kaleidoscope is an example of a "portable language": any program written
+in Kaleidoscope will work the same way on any target that it runs on.
+Many other languages have this property, e.g. lisp, java, haskell,
+javascript, python, etc (note that while these languages are portable,
+not all their libraries are).
+
+One nice aspect of LLVM is that it is often capable of preserving target
+independence in the IR: you can take the LLVM IR for a
+Kaleidoscope-compiled program and run it on any target that LLVM
+supports, even emitting C code and compiling that on targets that LLVM
+doesn't support natively. You can trivially tell that the Kaleidoscope
+compiler generates target-independent code because it never queries for
+any target-specific information when generating code.
+
+The fact that LLVM provides a compact, target-independent,
+representation for code gets a lot of people excited. Unfortunately,
+these people are usually thinking about C or a language from the C
+family when they are asking questions about language portability. I say
+"unfortunately", because there is really no way to make (fully general)
+C code portable, other than shipping the source code around (and of
+course, C source code is not actually portable in general either - ever
+port a really old application from 32- to 64-bits?).
+
+The problem with C (again, in its full generality) is that it is heavily
+laden with target specific assumptions. As one simple example, the
+preprocessor often destructively removes target-independence from the
+code when it processes the input text:
+
+.. code-block:: c
+
+    #ifdef __i386__
+      int X = 1;
+    #else
+      int X = 42;
+    #endif
+
+While it is possible to engineer more and more complex solutions to
+problems like this, it cannot be solved in full generality in a way that
+is better than shipping the actual source code.
+
+That said, there are interesting subsets of C that can be made portable.
+If you are willing to fix primitive types to a fixed size (say int =
+32-bits, and long = 64-bits), don't care about ABI compatibility with
+existing binaries, and are willing to give up some other minor features,
+you can have portable code. This can make sense for specialized domains
+such as an in-kernel language.
+
+Safety Guarantees
+-----------------
+
+Many of the languages above are also "safe" languages: it is impossible
+for a program written in Java to corrupt its address space and crash the
+process (assuming the JVM has no bugs). Safety is an interesting
+property that requires a combination of language design, runtime
+support, and often operating system support.
+
+It is certainly possible to implement a safe language in LLVM, but LLVM
+IR does not itself guarantee safety. The LLVM IR allows unsafe pointer
+casts, use after free bugs, buffer over-runs, and a variety of other
+problems. Safety needs to be implemented as a layer on top of LLVM and,
+conveniently, several groups have investigated this. Ask on the `llvm-dev
+mailing list <http://lists.llvm.org/mailman/listinfo/llvm-dev>`_ if
+you are interested in more details.
+
+Language-Specific Optimizations
+-------------------------------
+
+One thing about LLVM that turns off many people is that it does not
+solve all the world's problems in one system (sorry 'world hunger',
+someone else will have to solve you some other day). One specific
+complaint is that people perceive LLVM as being incapable of performing
+high-level language-specific optimization: LLVM "loses too much
+information".
+
+Unfortunately, this is really not the place to give you a full and
+unified version of "Chris Lattner's theory of compiler design". Instead,
+I'll make a few observations:
+
+First, you're right that LLVM does lose information. For example, as of
+this writing, there is no way to distinguish in the LLVM IR whether an
+SSA-value came from a C "int" or a C "long" on an ILP32 machine (other
+than debug info). Both get compiled down to an 'i32' value and the
+information about what it came from is lost. The more general issue
+here, is that the LLVM type system uses "structural equivalence" instead
+of "name equivalence". Another place this surprises people is if you
+have two types in a high-level language that have the same structure
+(e.g. two different structs that have a single int field): these types
+will compile down into a single LLVM type and it will be impossible to
+tell what it came from.
+
+Second, while LLVM does lose information, LLVM is not a fixed target: we
+continue to enhance and improve it in many different ways. In addition
+to adding new features (LLVM did not always support exceptions or debug
+info), we also extend the IR to capture important information for
+optimization (e.g. whether an argument is sign or zero extended,
+information about pointers aliasing, etc). Many of the enhancements are
+user-driven: people want LLVM to include some specific feature, so they
+go ahead and extend it.
+
+Third, it is *possible and easy* to add language-specific optimizations,
+and you have a number of choices in how to do it. As one trivial
+example, it is easy to add language-specific optimization passes that
+"know" things about code compiled for a language. In the case of the C
+family, there is an optimization pass that "knows" about the standard C
+library functions. If you call "exit(0)" in main(), it knows that it is
+safe to optimize that into "return 0;" because C specifies what the
+'exit' function does.
+
+In addition to simple library knowledge, it is possible to embed a
+variety of other language-specific information into the LLVM IR. If you
+have a specific need and run into a wall, please bring the topic up on
+the llvm-dev list. At the very worst, you can always treat LLVM as if it
+were a "dumb code generator" and implement the high-level optimizations
+you desire in your front-end, on the language-specific AST.
+
+Tips and Tricks
+===============
+
+There is a variety of useful tips and tricks that you come to know after
+working on/with LLVM that aren't obvious at first glance. Instead of
+letting everyone rediscover them, this section talks about some of these
+issues.
+
+Implementing portable offsetof/sizeof
+-------------------------------------
+
+One interesting thing that comes up, if you are trying to keep the code
+generated by your compiler "target independent", is that you often need
+to know the size of some LLVM type or the offset of some field in an
+llvm structure. For example, you might need to pass the size of a type
+into a function that allocates memory.
+
+Unfortunately, this can vary widely across targets: for example the
+width of a pointer is trivially target-specific. However, there is a
+`clever way to use the getelementptr
+instruction <http://nondot.org/sabre/LLVMNotes/SizeOf-OffsetOf-VariableSizedStructs.txt>`_
+that allows you to compute this in a portable way.
+
+Garbage Collected Stack Frames
+------------------------------
+
+Some languages want to explicitly manage their stack frames, often so
+that they are garbage collected or to allow easy implementation of
+closures. There are often better ways to implement these features than
+explicit stack frames, but `LLVM does support
+them, <http://nondot.org/sabre/LLVMNotes/ExplicitlyManagedStackFrames.txt>`_
+if you want. It requires your front-end to convert the code into
+`Continuation Passing
+Style <http://en.wikipedia.org/wiki/Continuation-passing_style>`_ and
+the use of tail calls (which LLVM also supports).
+

Added: www-releases/trunk/3.9.1/docs/_sources/tutorial/index.txt
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_sources/tutorial/index.txt?rev=290368&view=auto
==============================================================================
--- www-releases/trunk/3.9.1/docs/_sources/tutorial/index.txt (added)
+++ www-releases/trunk/3.9.1/docs/_sources/tutorial/index.txt Thu Dec 22 14:04:03 2016
@@ -0,0 +1,53 @@
+================================
+LLVM Tutorial: Table of Contents
+================================
+
+Kaleidoscope: Implementing a Language with LLVM
+===============================================
+
+.. toctree::
+   :titlesonly:
+   :glob:
+   :numbered:
+
+   LangImpl*
+
+Kaleidoscope: Implementing a Language with LLVM in Objective Caml
+=================================================================
+
+.. toctree::
+   :titlesonly:
+   :glob:
+   :numbered:
+
+   OCamlLangImpl*
+
+Building a JIT in LLVM
+===============================================
+
+.. toctree::
+   :titlesonly:
+   :glob:
+   :numbered:
+
+   BuildingAJIT*
+
+External Tutorials
+==================
+
+`Tutorial: Creating an LLVM Backend for the Cpu0 Architecture <http://jonathan2251.github.com/lbd/>`_
+   A step-by-step tutorial for developing an LLVM backend. Under
+   active development at `<https://github.com/Jonathan2251/lbd>`_ (please
+   contribute!).
+
+`Howto: Implementing LLVM Integrated Assembler`_
+   A simple guide for how to implement an LLVM integrated assembler for an
+   architecture.
+
+.. _`Howto: Implementing LLVM Integrated Assembler`: http://www.embecosm.com/appnotes/ean10/ean10-howto-llvmas-1.0.html
+
+Advanced Topics
+===============
+
+#. `Writing an Optimization for LLVM <http://llvm.org/pubs/2004-09-22-LCPCLLVMTutorial.html>`_
+

Added: www-releases/trunk/3.9.1/docs/_sources/yaml2obj.txt
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_sources/yaml2obj.txt?rev=290368&view=auto
==============================================================================
--- www-releases/trunk/3.9.1/docs/_sources/yaml2obj.txt (added)
+++ www-releases/trunk/3.9.1/docs/_sources/yaml2obj.txt Thu Dec 22 14:04:03 2016
@@ -0,0 +1,221 @@
+yaml2obj
+========
+
+yaml2obj takes a YAML description of an object file and converts it to a binary
+file.
+
+    $ yaml2obj input-file
+
+.. program:: yaml2obj
+
+Outputs the binary to stdout.
+
+COFF Syntax
+-----------
+
+Here's a sample COFF file.
+
+.. code-block:: yaml
+
+  header:
+    Machine: IMAGE_FILE_MACHINE_I386 # (0x14C)
+
+  sections:
+    - Name: .text
+      Characteristics: [ IMAGE_SCN_CNT_CODE
+                       , IMAGE_SCN_ALIGN_16BYTES
+                       , IMAGE_SCN_MEM_EXECUTE
+                       , IMAGE_SCN_MEM_READ
+                       ] # 0x60500020
+      SectionData:
+        "\x83\xEC\x0C\xC7\x44\x24\x08\x00\x00\x00\x00\xC7\x04\x24\x00\x00\x00\x00\xE8\x00\x00\x00\x00\xE8\x00\x00\x00\x00\x8B\x44\x24\x08\x83\xC4\x0C\xC3" # |....D$.......$...............D$.....|
+
+  symbols:
+    - Name: .text
+      Value: 0
+      SectionNumber: 1
+      SimpleType: IMAGE_SYM_TYPE_NULL # (0)
+      ComplexType: IMAGE_SYM_DTYPE_NULL # (0)
+      StorageClass: IMAGE_SYM_CLASS_STATIC # (3)
+      NumberOfAuxSymbols: 1
+      AuxiliaryData:
+        "\x24\x00\x00\x00\x03\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00" # |$.................|
+
+    - Name: _main
+      Value: 0
+      SectionNumber: 1
+      SimpleType: IMAGE_SYM_TYPE_NULL # (0)
+      ComplexType: IMAGE_SYM_DTYPE_NULL # (0)
+      StorageClass: IMAGE_SYM_CLASS_EXTERNAL # (2)
+
+Here's a simplified Kwalify_ schema with an extension to allow alternate types.
+
+.. _Kwalify: http://www.kuwata-lab.com/kwalify/ruby/users-guide.html
+
+.. code-block:: yaml
+
+  type: map
+    mapping:
+      header:
+        type: map
+        mapping:
+          Machine: [ {type: str, enum:
+                                 [ IMAGE_FILE_MACHINE_UNKNOWN
+                                 , IMAGE_FILE_MACHINE_AM33
+                                 , IMAGE_FILE_MACHINE_AMD64
+                                 , IMAGE_FILE_MACHINE_ARM
+                                 , IMAGE_FILE_MACHINE_ARMNT
+                                 , IMAGE_FILE_MACHINE_ARM64
+                                 , IMAGE_FILE_MACHINE_EBC
+                                 , IMAGE_FILE_MACHINE_I386
+                                 , IMAGE_FILE_MACHINE_IA64
+                                 , IMAGE_FILE_MACHINE_M32R
+                                 , IMAGE_FILE_MACHINE_MIPS16
+                                 , IMAGE_FILE_MACHINE_MIPSFPU
+                                 , IMAGE_FILE_MACHINE_MIPSFPU16
+                                 , IMAGE_FILE_MACHINE_POWERPC
+                                 , IMAGE_FILE_MACHINE_POWERPCFP
+                                 , IMAGE_FILE_MACHINE_R4000
+                                 , IMAGE_FILE_MACHINE_SH3
+                                 , IMAGE_FILE_MACHINE_SH3DSP
+                                 , IMAGE_FILE_MACHINE_SH4
+                                 , IMAGE_FILE_MACHINE_SH5
+                                 , IMAGE_FILE_MACHINE_THUMB
+                                 , IMAGE_FILE_MACHINE_WCEMIPSV2
+                                 ]}
+                   , {type: int}
+                   ]
+          Characteristics:
+            - type: seq
+              sequence:
+                - type: str
+                  enum: [ IMAGE_FILE_RELOCS_STRIPPED
+                        , IMAGE_FILE_EXECUTABLE_IMAGE
+                        , IMAGE_FILE_LINE_NUMS_STRIPPED
+                        , IMAGE_FILE_LOCAL_SYMS_STRIPPED
+                        , IMAGE_FILE_AGGRESSIVE_WS_TRIM
+                        , IMAGE_FILE_LARGE_ADDRESS_AWARE
+                        , IMAGE_FILE_BYTES_REVERSED_LO
+                        , IMAGE_FILE_32BIT_MACHINE
+                        , IMAGE_FILE_DEBUG_STRIPPED
+                        , IMAGE_FILE_REMOVABLE_RUN_FROM_SWAP
+                        , IMAGE_FILE_NET_RUN_FROM_SWAP
+                        , IMAGE_FILE_SYSTEM
+                        , IMAGE_FILE_DLL
+                        , IMAGE_FILE_UP_SYSTEM_ONLY
+                        , IMAGE_FILE_BYTES_REVERSED_HI
+                        ]
+            - type: int
+      sections:
+        type: seq
+        sequence:
+          - type: map
+            mapping:
+              Name: {type: str}
+              Characteristics:
+                - type: seq
+                  sequence:
+                    - type: str
+                      enum: [ IMAGE_SCN_TYPE_NO_PAD
+                            , IMAGE_SCN_CNT_CODE
+                            , IMAGE_SCN_CNT_INITIALIZED_DATA
+                            , IMAGE_SCN_CNT_UNINITIALIZED_DATA
+                            , IMAGE_SCN_LNK_OTHER
+                            , IMAGE_SCN_LNK_INFO
+                            , IMAGE_SCN_LNK_REMOVE
+                            , IMAGE_SCN_LNK_COMDAT
+                            , IMAGE_SCN_GPREL
+                            , IMAGE_SCN_MEM_PURGEABLE
+                            , IMAGE_SCN_MEM_16BIT
+                            , IMAGE_SCN_MEM_LOCKED
+                            , IMAGE_SCN_MEM_PRELOAD
+                            , IMAGE_SCN_ALIGN_1BYTES
+                            , IMAGE_SCN_ALIGN_2BYTES
+                            , IMAGE_SCN_ALIGN_4BYTES
+                            , IMAGE_SCN_ALIGN_8BYTES
+                            , IMAGE_SCN_ALIGN_16BYTES
+                            , IMAGE_SCN_ALIGN_32BYTES
+                            , IMAGE_SCN_ALIGN_64BYTES
+                            , IMAGE_SCN_ALIGN_128BYTES
+                            , IMAGE_SCN_ALIGN_256BYTES
+                            , IMAGE_SCN_ALIGN_512BYTES
+                            , IMAGE_SCN_ALIGN_1024BYTES
+                            , IMAGE_SCN_ALIGN_2048BYTES
+                            , IMAGE_SCN_ALIGN_4096BYTES
+                            , IMAGE_SCN_ALIGN_8192BYTES
+                            , IMAGE_SCN_LNK_NRELOC_OVFL
+                            , IMAGE_SCN_MEM_DISCARDABLE
+                            , IMAGE_SCN_MEM_NOT_CACHED
+                            , IMAGE_SCN_MEM_NOT_PAGED
+                            , IMAGE_SCN_MEM_SHARED
+                            , IMAGE_SCN_MEM_EXECUTE
+                            , IMAGE_SCN_MEM_READ
+                            , IMAGE_SCN_MEM_WRITE
+                            ]
+                - type: int
+              SectionData: {type: str}
+      symbols:
+        type: seq
+        sequence:
+          - type: map
+            mapping:
+              Name: {type: str}
+              Value: {type: int}
+              SectionNumber: {type: int}
+              SimpleType: [ {type: str, enum: [ IMAGE_SYM_TYPE_NULL
+                                              , IMAGE_SYM_TYPE_VOID
+                                              , IMAGE_SYM_TYPE_CHAR
+                                              , IMAGE_SYM_TYPE_SHORT
+                                              , IMAGE_SYM_TYPE_INT
+                                              , IMAGE_SYM_TYPE_LONG
+                                              , IMAGE_SYM_TYPE_FLOAT
+                                              , IMAGE_SYM_TYPE_DOUBLE
+                                              , IMAGE_SYM_TYPE_STRUCT
+                                              , IMAGE_SYM_TYPE_UNION
+                                              , IMAGE_SYM_TYPE_ENUM
+                                              , IMAGE_SYM_TYPE_MOE
+                                              , IMAGE_SYM_TYPE_BYTE
+                                              , IMAGE_SYM_TYPE_WORD
+                                              , IMAGE_SYM_TYPE_UINT
+                                              , IMAGE_SYM_TYPE_DWORD
+                                              ]}
+                          , {type: int}
+                          ]
+              ComplexType: [ {type: str, enum: [ IMAGE_SYM_DTYPE_NULL
+                                               , IMAGE_SYM_DTYPE_POINTER
+                                               , IMAGE_SYM_DTYPE_FUNCTION
+                                               , IMAGE_SYM_DTYPE_ARRAY
+                                               ]}
+                           , {type: int}
+                           ]
+              StorageClass: [ {type: str, enum:
+                                          [ IMAGE_SYM_CLASS_END_OF_FUNCTION
+                                          , IMAGE_SYM_CLASS_NULL
+                                          , IMAGE_SYM_CLASS_AUTOMATIC
+                                          , IMAGE_SYM_CLASS_EXTERNAL
+                                          , IMAGE_SYM_CLASS_STATIC
+                                          , IMAGE_SYM_CLASS_REGISTER
+                                          , IMAGE_SYM_CLASS_EXTERNAL_DEF
+                                          , IMAGE_SYM_CLASS_LABEL
+                                          , IMAGE_SYM_CLASS_UNDEFINED_LABEL
+                                          , IMAGE_SYM_CLASS_MEMBER_OF_STRUCT
+                                          , IMAGE_SYM_CLASS_ARGUMENT
+                                          , IMAGE_SYM_CLASS_STRUCT_TAG
+                                          , IMAGE_SYM_CLASS_MEMBER_OF_UNION
+                                          , IMAGE_SYM_CLASS_UNION_TAG
+                                          , IMAGE_SYM_CLASS_TYPE_DEFINITION
+                                          , IMAGE_SYM_CLASS_UNDEFINED_STATIC
+                                          , IMAGE_SYM_CLASS_ENUM_TAG
+                                          , IMAGE_SYM_CLASS_MEMBER_OF_ENUM
+                                          , IMAGE_SYM_CLASS_REGISTER_PARAM
+                                          , IMAGE_SYM_CLASS_BIT_FIELD
+                                          , IMAGE_SYM_CLASS_BLOCK
+                                          , IMAGE_SYM_CLASS_FUNCTION
+                                          , IMAGE_SYM_CLASS_END_OF_STRUCT
+                                          , IMAGE_SYM_CLASS_FILE
+                                          , IMAGE_SYM_CLASS_SECTION
+                                          , IMAGE_SYM_CLASS_WEAK_EXTERNAL
+                                          , IMAGE_SYM_CLASS_CLR_TOKEN
+                                          ]}
+                            , {type: int}
+                            ]

Added: www-releases/trunk/3.9.1/docs/_static/ajax-loader.gif
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_static/ajax-loader.gif?rev=290368&view=auto
==============================================================================
Binary file - no diff available.

Propchange: www-releases/trunk/3.9.1/docs/_static/ajax-loader.gif
------------------------------------------------------------------------------
    svn:mime-type = image/gif

Added: www-releases/trunk/3.9.1/docs/_static/basic.css
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_static/basic.css?rev=290368&view=auto
==============================================================================
--- www-releases/trunk/3.9.1/docs/_static/basic.css (added)
+++ www-releases/trunk/3.9.1/docs/_static/basic.css Thu Dec 22 14:04:03 2016
@@ -0,0 +1,537 @@
+/*
+ * basic.css
+ * ~~~~~~~~~
+ *
+ * Sphinx stylesheet -- basic theme.
+ *
+ * :copyright: Copyright 2007-2014 by the Sphinx team, see AUTHORS.
+ * :license: BSD, see LICENSE for details.
+ *
+ */
+
+/* -- main layout ----------------------------------------------------------- */
+
+div.clearer {
+    clear: both;
+}
+
+/* -- relbar ---------------------------------------------------------------- */
+
+div.related {
+    width: 100%;
+    font-size: 90%;
+}
+
+div.related h3 {
+    display: none;
+}
+
+div.related ul {
+    margin: 0;
+    padding: 0 0 0 10px;
+    list-style: none;
+}
+
+div.related li {
+    display: inline;
+}
+
+div.related li.right {
+    float: right;
+    margin-right: 5px;
+}
+
+/* -- sidebar --------------------------------------------------------------- */
+
+div.sphinxsidebarwrapper {
+    padding: 10px 5px 0 10px;
+}
+
+div.sphinxsidebar {
+    float: left;
+    width: 230px;
+    margin-left: -100%;
+    font-size: 90%;
+}
+
+div.sphinxsidebar ul {
+    list-style: none;
+}
+
+div.sphinxsidebar ul ul,
+div.sphinxsidebar ul.want-points {
+    margin-left: 20px;
+    list-style: square;
+}
+
+div.sphinxsidebar ul ul {
+    margin-top: 0;
+    margin-bottom: 0;
+}
+
+div.sphinxsidebar form {
+    margin-top: 10px;
+}
+
+div.sphinxsidebar input {
+    border: 1px solid #98dbcc;
+    font-family: sans-serif;
+    font-size: 1em;
+}
+
+div.sphinxsidebar #searchbox input[type="text"] {
+    width: 170px;
+}
+
+div.sphinxsidebar #searchbox input[type="submit"] {
+    width: 30px;
+}
+
+img {
+    border: 0;
+    max-width: 100%;
+}
+
+/* -- search page ----------------------------------------------------------- */
+
+ul.search {
+    margin: 10px 0 0 20px;
+    padding: 0;
+}
+
+ul.search li {
+    padding: 5px 0 5px 20px;
+    background-image: url(file.png);
+    background-repeat: no-repeat;
+    background-position: 0 7px;
+}
+
+ul.search li a {
+    font-weight: bold;
+}
+
+ul.search li div.context {
+    color: #888;
+    margin: 2px 0 0 30px;
+    text-align: left;
+}
+
+ul.keywordmatches li.goodmatch a {
+    font-weight: bold;
+}
+
+/* -- index page ------------------------------------------------------------ */
+
+table.contentstable {
+    width: 90%;
+}
+
+table.contentstable p.biglink {
+    line-height: 150%;
+}
+
+a.biglink {
+    font-size: 1.3em;
+}
+
+span.linkdescr {
+    font-style: italic;
+    padding-top: 5px;
+    font-size: 90%;
+}
+
+/* -- general index --------------------------------------------------------- */
+
+table.indextable {
+    width: 100%;
+}
+
+table.indextable td {
+    text-align: left;
+    vertical-align: top;
+}
+
+table.indextable dl, table.indextable dd {
+    margin-top: 0;
+    margin-bottom: 0;
+}
+
+table.indextable tr.pcap {
+    height: 10px;
+}
+
+table.indextable tr.cap {
+    margin-top: 10px;
+    background-color: #f2f2f2;
+}
+
+img.toggler {
+    margin-right: 3px;
+    margin-top: 3px;
+    cursor: pointer;
+}
+
+div.modindex-jumpbox {
+    border-top: 1px solid #ddd;
+    border-bottom: 1px solid #ddd;
+    margin: 1em 0 1em 0;
+    padding: 0.4em;
+}
+
+div.genindex-jumpbox {
+    border-top: 1px solid #ddd;
+    border-bottom: 1px solid #ddd;
+    margin: 1em 0 1em 0;
+    padding: 0.4em;
+}
+
+/* -- general body styles --------------------------------------------------- */
+
+a.headerlink {
+    visibility: hidden;
+}
+
+h1:hover > a.headerlink,
+h2:hover > a.headerlink,
+h3:hover > a.headerlink,
+h4:hover > a.headerlink,
+h5:hover > a.headerlink,
+h6:hover > a.headerlink,
+dt:hover > a.headerlink {
+    visibility: visible;
+}
+
+div.body p.caption {
+    text-align: inherit;
+}
+
+div.body td {
+    text-align: left;
+}
+
+.field-list ul {
+    padding-left: 1em;
+}
+
+.first {
+    margin-top: 0 !important;
+}
+
+p.rubric {
+    margin-top: 30px;
+    font-weight: bold;
+}
+
+img.align-left, .figure.align-left, object.align-left {
+    clear: left;
+    float: left;
+    margin-right: 1em;
+}
+
+img.align-right, .figure.align-right, object.align-right {
+    clear: right;
+    float: right;
+    margin-left: 1em;
+}
+
+img.align-center, .figure.align-center, object.align-center {
+  display: block;
+  margin-left: auto;
+  margin-right: auto;
+}
+
+.align-left {
+    text-align: left;
+}
+
+.align-center {
+    text-align: center;
+}
+
+.align-right {
+    text-align: right;
+}
+
+/* -- sidebars -------------------------------------------------------------- */
+
+div.sidebar {
+    margin: 0 0 0.5em 1em;
+    border: 1px solid #ddb;
+    padding: 7px 7px 0 7px;
+    background-color: #ffe;
+    width: 40%;
+    float: right;
+}
+
+p.sidebar-title {
+    font-weight: bold;
+}
+
+/* -- topics ---------------------------------------------------------------- */
+
+div.topic {
+    border: 1px solid #ccc;
+    padding: 7px 7px 0 7px;
+    margin: 10px 0 10px 0;
+}
+
+p.topic-title {
+    font-size: 1.1em;
+    font-weight: bold;
+    margin-top: 10px;
+}
+
+/* -- admonitions ----------------------------------------------------------- */
+
+div.admonition {
+    margin-top: 10px;
+    margin-bottom: 10px;
+    padding: 7px;
+}
+
+div.admonition dt {
+    font-weight: bold;
+}
+
+div.admonition dl {
+    margin-bottom: 0;
+}
+
+p.admonition-title {
+    margin: 0px 10px 5px 0px;
+    font-weight: bold;
+}
+
+div.body p.centered {
+    text-align: center;
+    margin-top: 25px;
+}
+
+/* -- tables ---------------------------------------------------------------- */
+
+table.docutils {
+    border: 0;
+    border-collapse: collapse;
+}
+
+table.docutils td, table.docutils th {
+    padding: 1px 8px 1px 5px;
+    border-top: 0;
+    border-left: 0;
+    border-right: 0;
+    border-bottom: 1px solid #aaa;
+}
+
+table.field-list td, table.field-list th {
+    border: 0 !important;
+}
+
+table.footnote td, table.footnote th {
+    border: 0 !important;
+}
+
+th {
+    text-align: left;
+    padding-right: 5px;
+}
+
+table.citation {
+    border-left: solid 1px gray;
+    margin-left: 1px;
+}
+
+table.citation td {
+    border-bottom: none;
+}
+
+/* -- other body styles ----------------------------------------------------- */
+
+ol.arabic {
+    list-style: decimal;
+}
+
+ol.loweralpha {
+    list-style: lower-alpha;
+}
+
+ol.upperalpha {
+    list-style: upper-alpha;
+}
+
+ol.lowerroman {
+    list-style: lower-roman;
+}
+
+ol.upperroman {
+    list-style: upper-roman;
+}
+
+dl {
+    margin-bottom: 15px;
+}
+
+dd p {
+    margin-top: 0px;
+}
+
+dd ul, dd table {
+    margin-bottom: 10px;
+}
+
+dd {
+    margin-top: 3px;
+    margin-bottom: 10px;
+    margin-left: 30px;
+}
+
+dt:target, .highlighted {
+    background-color: #fbe54e;
+}
+
+dl.glossary dt {
+    font-weight: bold;
+    font-size: 1.1em;
+}
+
+.field-list ul {
+    margin: 0;
+    padding-left: 1em;
+}
+
+.field-list p {
+    margin: 0;
+}
+
+.optional {
+    font-size: 1.3em;
+}
+
+.versionmodified {
+    font-style: italic;
+}
+
+.system-message {
+    background-color: #fda;
+    padding: 5px;
+    border: 3px solid red;
+}
+
+.footnote:target  {
+    background-color: #ffa;
+}
+
+.line-block {
+    display: block;
+    margin-top: 1em;
+    margin-bottom: 1em;
+}
+
+.line-block .line-block {
+    margin-top: 0;
+    margin-bottom: 0;
+    margin-left: 1.5em;
+}
+
+.guilabel, .menuselection {
+    font-family: sans-serif;
+}
+
+.accelerator {
+    text-decoration: underline;
+}
+
+.classifier {
+    font-style: oblique;
+}
+
+abbr, acronym {
+    border-bottom: dotted 1px;
+    cursor: help;
+}
+
+/* -- code displays --------------------------------------------------------- */
+
+pre {
+    overflow: auto;
+    overflow-y: hidden;  /* fixes display issues on Chrome browsers */
+}
+
+td.linenos pre {
+    padding: 5px 0px;
+    border: 0;
+    background-color: transparent;
+    color: #aaa;
+}
+
+table.highlighttable {
+    margin-left: 0.5em;
+}
+
+table.highlighttable td {
+    padding: 0 0.5em 0 0.5em;
+}
+
+tt.descname {
+    background-color: transparent;
+    font-weight: bold;
+    font-size: 1.2em;
+}
+
+tt.descclassname {
+    background-color: transparent;
+}
+
+tt.xref, a tt {
+    background-color: transparent;
+    font-weight: bold;
+}
+
+h1 tt, h2 tt, h3 tt, h4 tt, h5 tt, h6 tt {
+    background-color: transparent;
+}
+
+.viewcode-link {
+    float: right;
+}
+
+.viewcode-back {
+    float: right;
+    font-family: sans-serif;
+}
+
+div.viewcode-block:target {
+    margin: -1px -10px;
+    padding: 0 10px;
+}
+
+/* -- math display ---------------------------------------------------------- */
+
+img.math {
+    vertical-align: middle;
+}
+
+div.body div.math p {
+    text-align: center;
+}
+
+span.eqno {
+    float: right;
+}
+
+/* -- printout stylesheet --------------------------------------------------- */
+
+ at media print {
+    div.document,
+    div.documentwrapper,
+    div.bodywrapper {
+        margin: 0 !important;
+        width: 100%;
+    }
+
+    div.sphinxsidebar,
+    div.related,
+    div.footer,
+    #top-link {
+        display: none;
+    }
+}
\ No newline at end of file

Added: www-releases/trunk/3.9.1/docs/_static/comment-bright.png
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_static/comment-bright.png?rev=290368&view=auto
==============================================================================
Binary file - no diff available.

Propchange: www-releases/trunk/3.9.1/docs/_static/comment-bright.png
------------------------------------------------------------------------------
    svn:mime-type = image/png

Added: www-releases/trunk/3.9.1/docs/_static/comment-close.png
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_static/comment-close.png?rev=290368&view=auto
==============================================================================
Binary file - no diff available.

Propchange: www-releases/trunk/3.9.1/docs/_static/comment-close.png
------------------------------------------------------------------------------
    svn:mime-type = image/png

Added: www-releases/trunk/3.9.1/docs/_static/comment.png
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_static/comment.png?rev=290368&view=auto
==============================================================================
Binary file - no diff available.

Propchange: www-releases/trunk/3.9.1/docs/_static/comment.png
------------------------------------------------------------------------------
    svn:mime-type = image/png

Added: www-releases/trunk/3.9.1/docs/_static/contents.png
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_static/contents.png?rev=290368&view=auto
==============================================================================
Binary file - no diff available.

Propchange: www-releases/trunk/3.9.1/docs/_static/contents.png
------------------------------------------------------------------------------
    svn:mime-type = image/png

Added: www-releases/trunk/3.9.1/docs/_static/doctools.js
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_static/doctools.js?rev=290368&view=auto
==============================================================================
--- www-releases/trunk/3.9.1/docs/_static/doctools.js (added)
+++ www-releases/trunk/3.9.1/docs/_static/doctools.js Thu Dec 22 14:04:03 2016
@@ -0,0 +1,238 @@
+/*
+ * doctools.js
+ * ~~~~~~~~~~~
+ *
+ * Sphinx JavaScript utilities for all documentation.
+ *
+ * :copyright: Copyright 2007-2014 by the Sphinx team, see AUTHORS.
+ * :license: BSD, see LICENSE for details.
+ *
+ */
+
+/**
+ * select a different prefix for underscore
+ */
+$u = _.noConflict();
+
+/**
+ * make the code below compatible with browsers without
+ * an installed firebug like debugger
+if (!window.console || !console.firebug) {
+  var names = ["log", "debug", "info", "warn", "error", "assert", "dir",
+    "dirxml", "group", "groupEnd", "time", "timeEnd", "count", "trace",
+    "profile", "profileEnd"];
+  window.console = {};
+  for (var i = 0; i < names.length; ++i)
+    window.console[names[i]] = function() {};
+}
+ */
+
+/**
+ * small helper function to urldecode strings
+ */
+jQuery.urldecode = function(x) {
+  return decodeURIComponent(x).replace(/\+/g, ' ');
+};
+
+/**
+ * small helper function to urlencode strings
+ */
+jQuery.urlencode = encodeURIComponent;
+
+/**
+ * This function returns the parsed url parameters of the
+ * current request. Multiple values per key are supported,
+ * it will always return arrays of strings for the value parts.
+ */
+jQuery.getQueryParameters = function(s) {
+  if (typeof s == 'undefined')
+    s = document.location.search;
+  var parts = s.substr(s.indexOf('?') + 1).split('&');
+  var result = {};
+  for (var i = 0; i < parts.length; i++) {
+    var tmp = parts[i].split('=', 2);
+    var key = jQuery.urldecode(tmp[0]);
+    var value = jQuery.urldecode(tmp[1]);
+    if (key in result)
+      result[key].push(value);
+    else
+      result[key] = [value];
+  }
+  return result;
+};
+
+/**
+ * highlight a given string on a jquery object by wrapping it in
+ * span elements with the given class name.
+ */
+jQuery.fn.highlightText = function(text, className) {
+  function highlight(node) {
+    if (node.nodeType == 3) {
+      var val = node.nodeValue;
+      var pos = val.toLowerCase().indexOf(text);
+      if (pos >= 0 && !jQuery(node.parentNode).hasClass(className)) {
+        var span = document.createElement("span");
+        span.className = className;
+        span.appendChild(document.createTextNode(val.substr(pos, text.length)));
+        node.parentNode.insertBefore(span, node.parentNode.insertBefore(
+          document.createTextNode(val.substr(pos + text.length)),
+          node.nextSibling));
+        node.nodeValue = val.substr(0, pos);
+      }
+    }
+    else if (!jQuery(node).is("button, select, textarea")) {
+      jQuery.each(node.childNodes, function() {
+        highlight(this);
+      });
+    }
+  }
+  return this.each(function() {
+    highlight(this);
+  });
+};
+
+/**
+ * Small JavaScript module for the documentation.
+ */
+var Documentation = {
+
+  init : function() {
+    this.fixFirefoxAnchorBug();
+    this.highlightSearchWords();
+    this.initIndexTable();
+  },
+
+  /**
+   * i18n support
+   */
+  TRANSLATIONS : {},
+  PLURAL_EXPR : function(n) { return n == 1 ? 0 : 1; },
+  LOCALE : 'unknown',
+
+  // gettext and ngettext don't access this so that the functions
+  // can safely bound to a different name (_ = Documentation.gettext)
+  gettext : function(string) {
+    var translated = Documentation.TRANSLATIONS[string];
+    if (typeof translated == 'undefined')
+      return string;
+    return (typeof translated == 'string') ? translated : translated[0];
+  },
+
+  ngettext : function(singular, plural, n) {
+    var translated = Documentation.TRANSLATIONS[singular];
+    if (typeof translated == 'undefined')
+      return (n == 1) ? singular : plural;
+    return translated[Documentation.PLURALEXPR(n)];
+  },
+
+  addTranslations : function(catalog) {
+    for (var key in catalog.messages)
+      this.TRANSLATIONS[key] = catalog.messages[key];
+    this.PLURAL_EXPR = new Function('n', 'return +(' + catalog.plural_expr + ')');
+    this.LOCALE = catalog.locale;
+  },
+
+  /**
+   * add context elements like header anchor links
+   */
+  addContextElements : function() {
+    $('div[id] > :header:first').each(function() {
+      $('<a class="headerlink">\u00B6</a>').
+      attr('href', '#' + this.id).
+      attr('title', _('Permalink to this headline')).
+      appendTo(this);
+    });
+    $('dt[id]').each(function() {
+      $('<a class="headerlink">\u00B6</a>').
+      attr('href', '#' + this.id).
+      attr('title', _('Permalink to this definition')).
+      appendTo(this);
+    });
+  },
+
+  /**
+   * workaround a firefox stupidity
+   */
+  fixFirefoxAnchorBug : function() {
+    if (document.location.hash && $.browser.mozilla)
+      window.setTimeout(function() {
+        document.location.href += '';
+      }, 10);
+  },
+
+  /**
+   * highlight the search words provided in the url in the text
+   */
+  highlightSearchWords : function() {
+    var params = $.getQueryParameters();
+    var terms = (params.highlight) ? params.highlight[0].split(/\s+/) : [];
+    if (terms.length) {
+      var body = $('div.body');
+      if (!body.length) {
+        body = $('body');
+      }
+      window.setTimeout(function() {
+        $.each(terms, function() {
+          body.highlightText(this.toLowerCase(), 'highlighted');
+        });
+      }, 10);
+      $('<p class="highlight-link"><a href="javascript:Documentation.' +
+        'hideSearchWords()">' + _('Hide Search Matches') + '</a></p>')
+          .appendTo($('#searchbox'));
+    }
+  },
+
+  /**
+   * init the domain index toggle buttons
+   */
+  initIndexTable : function() {
+    var togglers = $('img.toggler').click(function() {
+      var src = $(this).attr('src');
+      var idnum = $(this).attr('id').substr(7);
+      $('tr.cg-' + idnum).toggle();
+      if (src.substr(-9) == 'minus.png')
+        $(this).attr('src', src.substr(0, src.length-9) + 'plus.png');
+      else
+        $(this).attr('src', src.substr(0, src.length-8) + 'minus.png');
+    }).css('display', '');
+    if (DOCUMENTATION_OPTIONS.COLLAPSE_INDEX) {
+        togglers.click();
+    }
+  },
+
+  /**
+   * helper function to hide the search marks again
+   */
+  hideSearchWords : function() {
+    $('#searchbox .highlight-link').fadeOut(300);
+    $('span.highlighted').removeClass('highlighted');
+  },
+
+  /**
+   * make the url absolute
+   */
+  makeURL : function(relativeURL) {
+    return DOCUMENTATION_OPTIONS.URL_ROOT + '/' + relativeURL;
+  },
+
+  /**
+   * get the current relative url
+   */
+  getCurrentURL : function() {
+    var path = document.location.pathname;
+    var parts = path.split(/\//);
+    $.each(DOCUMENTATION_OPTIONS.URL_ROOT.split(/\//), function() {
+      if (this == '..')
+        parts.pop();
+    });
+    var url = parts.join('/');
+    return path.substring(url.lastIndexOf('/') + 1, path.length - 1);
+  }
+};
+
+// quick alias for translations
+_ = Documentation.gettext;
+
+$(document).ready(function() {
+  Documentation.init();
+});

Added: www-releases/trunk/3.9.1/docs/_static/down-pressed.png
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_static/down-pressed.png?rev=290368&view=auto
==============================================================================
Binary file - no diff available.

Propchange: www-releases/trunk/3.9.1/docs/_static/down-pressed.png
------------------------------------------------------------------------------
    svn:mime-type = image/png

Added: www-releases/trunk/3.9.1/docs/_static/down.png
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_static/down.png?rev=290368&view=auto
==============================================================================
Binary file - no diff available.

Propchange: www-releases/trunk/3.9.1/docs/_static/down.png
------------------------------------------------------------------------------
    svn:mime-type = image/png

Added: www-releases/trunk/3.9.1/docs/_static/file.png
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_static/file.png?rev=290368&view=auto
==============================================================================
Binary file - no diff available.

Propchange: www-releases/trunk/3.9.1/docs/_static/file.png
------------------------------------------------------------------------------
    svn:mime-type = image/png

Added: www-releases/trunk/3.9.1/docs/_static/jquery.js
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_static/jquery.js?rev=290368&view=auto
==============================================================================
--- www-releases/trunk/3.9.1/docs/_static/jquery.js (added)
+++ www-releases/trunk/3.9.1/docs/_static/jquery.js Thu Dec 22 14:04:03 2016
@@ -0,0 +1,2 @@
+/*! jQuery v1.8.3 jquery.com | jquery.org/license */
+(function(e,t){function _(e){var t=M[e]={};return v.each(e.split(y),function(e,n){t[n]=!0}),t}function H(e,n,r){if(r===t&&e.nodeType===1){var i="data-"+n.replace(P,"-$1").toLowerCase();r=e.getAttribute(i);if(typeof r=="string"){try{r=r==="true"?!0:r==="false"?!1:r==="null"?null:+r+""===r?+r:D.test(r)?v.parseJSON(r):r}catch(s){}v.data(e,n,r)}else r=t}return r}function B(e){var t;for(t in e){if(t==="data"&&v.isEmptyObject(e[t]))continue;if(t!=="toJSON")return!1}return!0}function et(){return!1}function tt(){return!0}function ut(e){return!e||!e.parentNode||e.parentNode.nodeType===11}function at(e,t){do e=e[t];while(e&&e.nodeType!==1);return e}function ft(e,t,n){t=t||0;if(v.isFunction(t))return v.grep(e,function(e,r){var i=!!t.call(e,r,e);return i===n});if(t.nodeType)return v.grep(e,function(e,r){return e===t===n});if(typeof t=="string"){var r=v.grep(e,function(e){return e.nodeType===1});if(it.test(t))return v.filter(t,r,!n);t=v.filter(t,r)}return v.grep(e,function(e,r){return v.inArray(
 e,t)>=0===n})}function lt(e){var t=ct.split("|"),n=e.createDocumentFragment();if(n.createElement)while(t.length)n.createElement(t.pop());return n}function Lt(e,t){return e.getElementsByTagName(t)[0]||e.appendChild(e.ownerDocument.createElement(t))}function At(e,t){if(t.nodeType!==1||!v.hasData(e))return;var n,r,i,s=v._data(e),o=v._data(t,s),u=s.events;if(u){delete o.handle,o.events={};for(n in u)for(r=0,i=u[n].length;r<i;r++)v.event.add(t,n,u[n][r])}o.data&&(o.data=v.extend({},o.data))}function Ot(e,t){var n;if(t.nodeType!==1)return;t.clearAttributes&&t.clearAttributes(),t.mergeAttributes&&t.mergeAttributes(e),n=t.nodeName.toLowerCase(),n==="object"?(t.parentNode&&(t.outerHTML=e.outerHTML),v.support.html5Clone&&e.innerHTML&&!v.trim(t.innerHTML)&&(t.innerHTML=e.innerHTML)):n==="input"&&Et.test(e.type)?(t.defaultChecked=t.checked=e.checked,t.value!==e.value&&(t.value=e.value)):n==="option"?t.selected=e.defaultSelected:n==="input"||n==="textarea"?t.defaultValue=e.defaultValue:n==="scri
 pt"&&t.text!==e.text&&(t.text=e.text),t.removeAttribute(v.expando)}function Mt(e){return typeof e.getElementsByTagName!="undefined"?e.getElementsByTagName("*"):typeof e.querySelectorAll!="undefined"?e.querySelectorAll("*"):[]}function _t(e){Et.test(e.type)&&(e.defaultChecked=e.checked)}function Qt(e,t){if(t in e)return t;var n=t.charAt(0).toUpperCase()+t.slice(1),r=t,i=Jt.length;while(i--){t=Jt[i]+n;if(t in e)return t}return r}function Gt(e,t){return e=t||e,v.css(e,"display")==="none"||!v.contains(e.ownerDocument,e)}function Yt(e,t){var n,r,i=[],s=0,o=e.length;for(;s<o;s++){n=e[s];if(!n.style)continue;i[s]=v._data(n,"olddisplay"),t?(!i[s]&&n.style.display==="none"&&(n.style.display=""),n.style.display===""&&Gt(n)&&(i[s]=v._data(n,"olddisplay",nn(n.nodeName)))):(r=Dt(n,"display"),!i[s]&&r!=="none"&&v._data(n,"olddisplay",r))}for(s=0;s<o;s++){n=e[s];if(!n.style)continue;if(!t||n.style.display==="none"||n.style.display==="")n.style.display=t?i[s]||"":"none"}return e}function Zt(e,t,n){
 var r=Rt.exec(t);return r?Math.max(0,r[1]-(n||0))+(r[2]||"px"):t}function en(e,t,n,r){var i=n===(r?"border":"content")?4:t==="width"?1:0,s=0;for(;i<4;i+=2)n==="margin"&&(s+=v.css(e,n+$t[i],!0)),r?(n==="content"&&(s-=parseFloat(Dt(e,"padding"+$t[i]))||0),n!=="margin"&&(s-=parseFloat(Dt(e,"border"+$t[i]+"Width"))||0)):(s+=parseFloat(Dt(e,"padding"+$t[i]))||0,n!=="padding"&&(s+=parseFloat(Dt(e,"border"+$t[i]+"Width"))||0));return s}function tn(e,t,n){var r=t==="width"?e.offsetWidth:e.offsetHeight,i=!0,s=v.support.boxSizing&&v.css(e,"boxSizing")==="border-box";if(r<=0||r==null){r=Dt(e,t);if(r<0||r==null)r=e.style[t];if(Ut.test(r))return r;i=s&&(v.support.boxSizingReliable||r===e.style[t]),r=parseFloat(r)||0}return r+en(e,t,n||(s?"border":"content"),i)+"px"}function nn(e){if(Wt[e])return Wt[e];var t=v("<"+e+">").appendTo(i.body),n=t.css("display");t.remove();if(n==="none"||n===""){Pt=i.body.appendChild(Pt||v.extend(i.createElement("iframe"),{frameBorder:0,width:0,height:0}));if(!Ht||!Pt.
 createElement)Ht=(Pt.contentWindow||Pt.contentDocument).document,Ht.write("<!doctype html><html><body>"),Ht.close();t=Ht.body.appendChild(Ht.createElement(e)),n=Dt(t,"display"),i.body.removeChild(Pt)}return Wt[e]=n,n}function fn(e,t,n,r){var i;if(v.isArray(t))v.each(t,function(t,i){n||sn.test(e)?r(e,i):fn(e+"["+(typeof i=="object"?t:"")+"]",i,n,r)});else if(!n&&v.type(t)==="object")for(i in t)fn(e+"["+i+"]",t[i],n,r);else r(e,t)}function Cn(e){return function(t,n){typeof t!="string"&&(n=t,t="*");var r,i,s,o=t.toLowerCase().split(y),u=0,a=o.length;if(v.isFunction(n))for(;u<a;u++)r=o[u],s=/^\+/.test(r),s&&(r=r.substr(1)||"*"),i=e[r]=e[r]||[],i[s?"unshift":"push"](n)}}function kn(e,n,r,i,s,o){s=s||n.dataTypes[0],o=o||{},o[s]=!0;var u,a=e[s],f=0,l=a?a.length:0,c=e===Sn;for(;f<l&&(c||!u);f++)u=a[f](n,r,i),typeof u=="string"&&(!c||o[u]?u=t:(n.dataTypes.unshift(u),u=kn(e,n,r,i,u,o)));return(c||!u)&&!o["*"]&&(u=kn(e,n,r,i,"*",o)),u}function Ln(e,n){var r,i,s=v.ajaxSettings.flatOptions||{};f
 or(r in n)n[r]!==t&&((s[r]?e:i||(i={}))[r]=n[r]);i&&v.extend(!0,e,i)}function An(e,n,r){var i,s,o,u,a=e.contents,f=e.dataTypes,l=e.responseFields;for(s in l)s in r&&(n[l[s]]=r[s]);while(f[0]==="*")f.shift(),i===t&&(i=e.mimeType||n.getResponseHeader("content-type"));if(i)for(s in a)if(a[s]&&a[s].test(i)){f.unshift(s);break}if(f[0]in r)o=f[0];else{for(s in r){if(!f[0]||e.converters[s+" "+f[0]]){o=s;break}u||(u=s)}o=o||u}if(o)return o!==f[0]&&f.unshift(o),r[o]}function On(e,t){var n,r,i,s,o=e.dataTypes.slice(),u=o[0],a={},f=0;e.dataFilter&&(t=e.dataFilter(t,e.dataType));if(o[1])for(n in e.converters)a[n.toLowerCase()]=e.converters[n];for(;i=o[++f];)if(i!=="*"){if(u!=="*"&&u!==i){n=a[u+" "+i]||a["* "+i];if(!n)for(r in a){s=r.split(" ");if(s[1]===i){n=a[u+" "+s[0]]||a["* "+s[0]];if(n){n===!0?n=a[r]:a[r]!==!0&&(i=s[0],o.splice(f--,0,i));break}}}if(n!==!0)if(n&&e["throws"])t=n(t);else try{t=n(t)}catch(l){return{state:"parsererror",error:n?l:"No conversion from "+u+" to "+i}}}u=i}return{sta
 te:"success",data:t}}function Fn(){try{return new e.XMLHttpRequest}catch(t){}}function In(){try{return new e.ActiveXObject("Microsoft.XMLHTTP")}catch(t){}}function $n(){return setTimeout(function(){qn=t},0),qn=v.now()}function Jn(e,t){v.each(t,function(t,n){var r=(Vn[t]||[]).concat(Vn["*"]),i=0,s=r.length;for(;i<s;i++)if(r[i].call(e,t,n))return})}function Kn(e,t,n){var r,i=0,s=0,o=Xn.length,u=v.Deferred().always(function(){delete a.elem}),a=function(){var t=qn||$n(),n=Math.max(0,f.startTime+f.duration-t),r=n/f.duration||0,i=1-r,s=0,o=f.tweens.length;for(;s<o;s++)f.tweens[s].run(i);return u.notifyWith(e,[f,i,n]),i<1&&o?n:(u.resolveWith(e,[f]),!1)},f=u.promise({elem:e,props:v.extend({},t),opts:v.extend(!0,{specialEasing:{}},n),originalProperties:t,originalOptions:n,startTime:qn||$n(),duration:n.duration,tweens:[],createTween:function(t,n,r){var i=v.Tween(e,f.opts,t,n,f.opts.specialEasing[t]||f.opts.easing);return f.tweens.push(i),i},stop:function(t){var n=0,r=t?f.tweens.length:0;for(;
 n<r;n++)f.tweens[n].run(1);return t?u.resolveWith(e,[f,t]):u.rejectWith(e,[f,t]),this}}),l=f.props;Qn(l,f.opts.specialEasing);for(;i<o;i++){r=Xn[i].call(f,e,l,f.opts);if(r)return r}return Jn(f,l),v.isFunction(f.opts.start)&&f.opts.start.call(e,f),v.fx.timer(v.extend(a,{anim:f,queue:f.opts.queue,elem:e})),f.progress(f.opts.progress).done(f.opts.done,f.opts.complete).fail(f.opts.fail).always(f.opts.always)}function Qn(e,t){var n,r,i,s,o;for(n in e){r=v.camelCase(n),i=t[r],s=e[n],v.isArray(s)&&(i=s[1],s=e[n]=s[0]),n!==r&&(e[r]=s,delete e[n]),o=v.cssHooks[r];if(o&&"expand"in o){s=o.expand(s),delete e[r];for(n in s)n in e||(e[n]=s[n],t[n]=i)}else t[r]=i}}function Gn(e,t,n){var r,i,s,o,u,a,f,l,c,h=this,p=e.style,d={},m=[],g=e.nodeType&&Gt(e);n.queue||(l=v._queueHooks(e,"fx"),l.unqueued==null&&(l.unqueued=0,c=l.empty.fire,l.empty.fire=function(){l.unqueued||c()}),l.unqueued++,h.always(function(){h.always(function(){l.unqueued--,v.queue(e,"fx").length||l.empty.fire()})})),e.nodeType===1&&("
 height"in t||"width"in t)&&(n.overflow=[p.overflow,p.overflowX,p.overflowY],v.css(e,"display")==="inline"&&v.css(e,"float")==="none"&&(!v.support.inlineBlockNeedsLayout||nn(e.nodeName)==="inline"?p.display="inline-block":p.zoom=1)),n.overflow&&(p.overflow="hidden",v.support.shrinkWrapBlocks||h.done(function(){p.overflow=n.overflow[0],p.overflowX=n.overflow[1],p.overflowY=n.overflow[2]}));for(r in t){s=t[r];if(Un.exec(s)){delete t[r],a=a||s==="toggle";if(s===(g?"hide":"show"))continue;m.push(r)}}o=m.length;if(o){u=v._data(e,"fxshow")||v._data(e,"fxshow",{}),"hidden"in u&&(g=u.hidden),a&&(u.hidden=!g),g?v(e).show():h.done(function(){v(e).hide()}),h.done(function(){var t;v.removeData(e,"fxshow",!0);for(t in d)v.style(e,t,d[t])});for(r=0;r<o;r++)i=m[r],f=h.createTween(i,g?u[i]:0),d[i]=u[i]||v.style(e,i),i in u||(u[i]=f.start,g&&(f.end=f.start,f.start=i==="width"||i==="height"?1:0))}}function Yn(e,t,n,r,i){return new Yn.prototype.init(e,t,n,r,i)}function Zn(e,t){var n,r={height:e},i=0;t=
 t?1:0;for(;i<4;i+=2-t)n=$t[i],r["margin"+n]=r["padding"+n]=e;return t&&(r.opacity=r.width=e),r}function tr(e){return v.isWindow(e)?e:e.nodeType===9?e.defaultView||e.parentWindow:!1}var n,r,i=e.document,s=e.location,o=e.navigator,u=e.jQuery,a=e.$,f=Array.prototype.push,l=Array.prototype.slice,c=Array.prototype.indexOf,h=Object.prototype.toString,p=Object.prototype.hasOwnProperty,d=String.prototype.trim,v=function(e,t){return new v.fn.init(e,t,n)},m=/[\-+]?(?:\d*\.|)\d+(?:[eE][\-+]?\d+|)/.source,g=/\S/,y=/\s+/,b=/^[\s\uFEFF\xA0]+|[\s\uFEFF\xA0]+$/g,w=/^(?:[^#<]*(<[\w\W]+>)[^>]*$|#([\w\-]*)$)/,E=/^<(\w+)\s*\/?>(?:<\/\1>|)$/,S=/^[\],:{}\s]*$/,x=/(?:^|:|,)(?:\s*\[)+/g,T=/\\(?:["\\\/bfnrt]|u[\da-fA-F]{4})/g,N=/"[^"\\\r\n]*"|true|false|null|-?(?:\d\d*\.|)\d+(?:[eE][\-+]?\d+|)/g,C=/^-ms-/,k=/-([\da-z])/gi,L=function(e,t){return(t+"").toUpperCase()},A=function(){i.addEventListener?(i.removeEventListener("DOMContentLoaded",A,!1),v.ready()):i.readyState==="complete"&&(i.detachEvent("onreadysta
 techange",A),v.ready())},O={};v.fn=v.prototype={constructor:v,init:function(e,n,r){var s,o,u,a;if(!e)return this;if(e.nodeType)return this.context=this[0]=e,this.length=1,this;if(typeof e=="string"){e.charAt(0)==="<"&&e.charAt(e.length-1)===">"&&e.length>=3?s=[null,e,null]:s=w.exec(e);if(s&&(s[1]||!n)){if(s[1])return n=n instanceof v?n[0]:n,a=n&&n.nodeType?n.ownerDocument||n:i,e=v.parseHTML(s[1],a,!0),E.test(s[1])&&v.isPlainObject(n)&&this.attr.call(e,n,!0),v.merge(this,e);o=i.getElementById(s[2]);if(o&&o.parentNode){if(o.id!==s[2])return r.find(e);this.length=1,this[0]=o}return this.context=i,this.selector=e,this}return!n||n.jquery?(n||r).find(e):this.constructor(n).find(e)}return v.isFunction(e)?r.ready(e):(e.selector!==t&&(this.selector=e.selector,this.context=e.context),v.makeArray(e,this))},selector:"",jquery:"1.8.3",length:0,size:function(){return this.length},toArray:function(){return l.call(this)},get:function(e){return e==null?this.toArray():e<0?this[this.length+e]:this[e]}
 ,pushStack:function(e,t,n){var r=v.merge(this.constructor(),e);return r.prevObject=this,r.context=this.context,t==="find"?r.selector=this.selector+(this.selector?" ":"")+n:t&&(r.selector=this.selector+"."+t+"("+n+")"),r},each:function(e,t){return v.each(this,e,t)},ready:function(e){return v.ready.promise().done(e),this},eq:function(e){return e=+e,e===-1?this.slice(e):this.slice(e,e+1)},first:function(){return this.eq(0)},last:function(){return this.eq(-1)},slice:function(){return this.pushStack(l.apply(this,arguments),"slice",l.call(arguments).join(","))},map:function(e){return this.pushStack(v.map(this,function(t,n){return e.call(t,n,t)}))},end:function(){return this.prevObject||this.constructor(null)},push:f,sort:[].sort,splice:[].splice},v.fn.init.prototype=v.fn,v.extend=v.fn.extend=function(){var e,n,r,i,s,o,u=arguments[0]||{},a=1,f=arguments.length,l=!1;typeof u=="boolean"&&(l=u,u=arguments[1]||{},a=2),typeof u!="object"&&!v.isFunction(u)&&(u={}),f===a&&(u=this,--a);for(;a<f;a+
 +)if((e=arguments[a])!=null)for(n in e){r=u[n],i=e[n];if(u===i)continue;l&&i&&(v.isPlainObject(i)||(s=v.isArray(i)))?(s?(s=!1,o=r&&v.isArray(r)?r:[]):o=r&&v.isPlainObject(r)?r:{},u[n]=v.extend(l,o,i)):i!==t&&(u[n]=i)}return u},v.extend({noConflict:function(t){return e.$===v&&(e.$=a),t&&e.jQuery===v&&(e.jQuery=u),v},isReady:!1,readyWait:1,holdReady:function(e){e?v.readyWait++:v.ready(!0)},ready:function(e){if(e===!0?--v.readyWait:v.isReady)return;if(!i.body)return setTimeout(v.ready,1);v.isReady=!0;if(e!==!0&&--v.readyWait>0)return;r.resolveWith(i,[v]),v.fn.trigger&&v(i).trigger("ready").off("ready")},isFunction:function(e){return v.type(e)==="function"},isArray:Array.isArray||function(e){return v.type(e)==="array"},isWindow:function(e){return e!=null&&e==e.window},isNumeric:function(e){return!isNaN(parseFloat(e))&&isFinite(e)},type:function(e){return e==null?String(e):O[h.call(e)]||"object"},isPlainObject:function(e){if(!e||v.type(e)!=="object"||e.nodeType||v.isWindow(e))return!1;tr
 y{if(e.constructor&&!p.call(e,"constructor")&&!p.call(e.constructor.prototype,"isPrototypeOf"))return!1}catch(n){return!1}var r;for(r in e);return r===t||p.call(e,r)},isEmptyObject:function(e){var t;for(t in e)return!1;return!0},error:function(e){throw new Error(e)},parseHTML:function(e,t,n){var r;return!e||typeof e!="string"?null:(typeof t=="boolean"&&(n=t,t=0),t=t||i,(r=E.exec(e))?[t.createElement(r[1])]:(r=v.buildFragment([e],t,n?null:[]),v.merge([],(r.cacheable?v.clone(r.fragment):r.fragment).childNodes)))},parseJSON:function(t){if(!t||typeof t!="string")return null;t=v.trim(t);if(e.JSON&&e.JSON.parse)return e.JSON.parse(t);if(S.test(t.replace(T,"@").replace(N,"]").replace(x,"")))return(new Function("return "+t))();v.error("Invalid JSON: "+t)},parseXML:function(n){var r,i;if(!n||typeof n!="string")return null;try{e.DOMParser?(i=new DOMParser,r=i.parseFromString(n,"text/xml")):(r=new ActiveXObject("Microsoft.XMLDOM"),r.async="false",r.loadXML(n))}catch(s){r=t}return(!r||!r.docume
 ntElement||r.getElementsByTagName("parsererror").length)&&v.error("Invalid XML: "+n),r},noop:function(){},globalEval:function(t){t&&g.test(t)&&(e.execScript||function(t){e.eval.call(e,t)})(t)},camelCase:function(e){return e.replace(C,"ms-").replace(k,L)},nodeName:function(e,t){return e.nodeName&&e.nodeName.toLowerCase()===t.toLowerCase()},each:function(e,n,r){var i,s=0,o=e.length,u=o===t||v.isFunction(e);if(r){if(u){for(i in e)if(n.apply(e[i],r)===!1)break}else for(;s<o;)if(n.apply(e[s++],r)===!1)break}else if(u){for(i in e)if(n.call(e[i],i,e[i])===!1)break}else for(;s<o;)if(n.call(e[s],s,e[s++])===!1)break;return e},trim:d&&!d.call("\ufeff\u00a0")?function(e){return e==null?"":d.call(e)}:function(e){return e==null?"":(e+"").replace(b,"")},makeArray:function(e,t){var n,r=t||[];return e!=null&&(n=v.type(e),e.length==null||n==="string"||n==="function"||n==="regexp"||v.isWindow(e)?f.call(r,e):v.merge(r,e)),r},inArray:function(e,t,n){var r;if(t){if(c)return c.call(t,e,n);r=t.length,n=n?
 n<0?Math.max(0,r+n):n:0;for(;n<r;n++)if(n in t&&t[n]===e)return n}return-1},merge:function(e,n){var r=n.length,i=e.length,s=0;if(typeof r=="number")for(;s<r;s++)e[i++]=n[s];else while(n[s]!==t)e[i++]=n[s++];return e.length=i,e},grep:function(e,t,n){var r,i=[],s=0,o=e.length;n=!!n;for(;s<o;s++)r=!!t(e[s],s),n!==r&&i.push(e[s]);return i},map:function(e,n,r){var i,s,o=[],u=0,a=e.length,f=e instanceof v||a!==t&&typeof a=="number"&&(a>0&&e[0]&&e[a-1]||a===0||v.isArray(e));if(f)for(;u<a;u++)i=n(e[u],u,r),i!=null&&(o[o.length]=i);else for(s in e)i=n(e[s],s,r),i!=null&&(o[o.length]=i);return o.concat.apply([],o)},guid:1,proxy:function(e,n){var r,i,s;return typeof n=="string"&&(r=e[n],n=e,e=r),v.isFunction(e)?(i=l.call(arguments,2),s=function(){return e.apply(n,i.concat(l.call(arguments)))},s.guid=e.guid=e.guid||v.guid++,s):t},access:function(e,n,r,i,s,o,u){var a,f=r==null,l=0,c=e.length;if(r&&typeof r=="object"){for(l in r)v.access(e,n,l,r[l],1,o,i);s=1}else if(i!==t){a=u===t&&v.isFunction(
 i),f&&(a?(a=n,n=function(e,t,n){return a.call(v(e),n)}):(n.call(e,i),n=null));if(n)for(;l<c;l++)n(e[l],r,a?i.call(e[l],l,n(e[l],r)):i,u);s=1}return s?e:f?n.call(e):c?n(e[0],r):o},now:function(){return(new Date).getTime()}}),v.ready.promise=function(t){if(!r){r=v.Deferred();if(i.readyState==="complete")setTimeout(v.ready,1);else if(i.addEventListener)i.addEventListener("DOMContentLoaded",A,!1),e.addEventListener("load",v.ready,!1);else{i.attachEvent("onreadystatechange",A),e.attachEvent("onload",v.ready);var n=!1;try{n=e.frameElement==null&&i.documentElement}catch(s){}n&&n.doScroll&&function o(){if(!v.isReady){try{n.doScroll("left")}catch(e){return setTimeout(o,50)}v.ready()}}()}}return r.promise(t)},v.each("Boolean Number String Function Array Date RegExp Object".split(" "),function(e,t){O["[object "+t+"]"]=t.toLowerCase()}),n=v(i);var M={};v.Callbacks=function(e){e=typeof e=="string"?M[e]||_(e):v.extend({},e);var n,r,i,s,o,u,a=[],f=!e.once&&[],l=function(t){n=e.memory&&t,r=!0,u=s||
 0,s=0,o=a.length,i=!0;for(;a&&u<o;u++)if(a[u].apply(t[0],t[1])===!1&&e.stopOnFalse){n=!1;break}i=!1,a&&(f?f.length&&l(f.shift()):n?a=[]:c.disable())},c={add:function(){if(a){var t=a.length;(function r(t){v.each(t,function(t,n){var i=v.type(n);i==="function"?(!e.unique||!c.has(n))&&a.push(n):n&&n.length&&i!=="string"&&r(n)})})(arguments),i?o=a.length:n&&(s=t,l(n))}return this},remove:function(){return a&&v.each(arguments,function(e,t){var n;while((n=v.inArray(t,a,n))>-1)a.splice(n,1),i&&(n<=o&&o--,n<=u&&u--)}),this},has:function(e){return v.inArray(e,a)>-1},empty:function(){return a=[],this},disable:function(){return a=f=n=t,this},disabled:function(){return!a},lock:function(){return f=t,n||c.disable(),this},locked:function(){return!f},fireWith:function(e,t){return t=t||[],t=[e,t.slice?t.slice():t],a&&(!r||f)&&(i?f.push(t):l(t)),this},fire:function(){return c.fireWith(this,arguments),this},fired:function(){return!!r}};return c},v.extend({Deferred:function(e){var t=[["resolve","done",v
 .Callbacks("once memory"),"resolved"],["reject","fail",v.Callbacks("once memory"),"rejected"],["notify","progress",v.Callbacks("memory")]],n="pending",r={state:function(){return n},always:function(){return i.done(arguments).fail(arguments),this},then:function(){var e=arguments;return v.Deferred(function(n){v.each(t,function(t,r){var s=r[0],o=e[t];i[r[1]](v.isFunction(o)?function(){var e=o.apply(this,arguments);e&&v.isFunction(e.promise)?e.promise().done(n.resolve).fail(n.reject).progress(n.notify):n[s+"With"](this===i?n:this,[e])}:n[s])}),e=null}).promise()},promise:function(e){return e!=null?v.extend(e,r):r}},i={};return r.pipe=r.then,v.each(t,function(e,s){var o=s[2],u=s[3];r[s[1]]=o.add,u&&o.add(function(){n=u},t[e^1][2].disable,t[2][2].lock),i[s[0]]=o.fire,i[s[0]+"With"]=o.fireWith}),r.promise(i),e&&e.call(i,i),i},when:function(e){var t=0,n=l.call(arguments),r=n.length,i=r!==1||e&&v.isFunction(e.promise)?r:0,s=i===1?e:v.Deferred(),o=function(e,t,n){return function(r){t[e]=this,n
 [e]=arguments.length>1?l.call(arguments):r,n===u?s.notifyWith(t,n):--i||s.resolveWith(t,n)}},u,a,f;if(r>1){u=new Array(r),a=new Array(r),f=new Array(r);for(;t<r;t++)n[t]&&v.isFunction(n[t].promise)?n[t].promise().done(o(t,f,n)).fail(s.reject).progress(o(t,a,u)):--i}return i||s.resolveWith(f,n),s.promise()}}),v.support=function(){var t,n,r,s,o,u,a,f,l,c,h,p=i.createElement("div");p.setAttribute("className","t"),p.innerHTML="  <link/><table></table><a href='/a'>a</a><input type='checkbox'/>",n=p.getElementsByTagName("*"),r=p.getElementsByTagName("a")[0];if(!n||!r||!n.length)return{};s=i.createElement("select"),o=s.appendChild(i.createElement("option")),u=p.getElementsByTagName("input")[0],r.style.cssText="top:1px;float:left;opacity:.5",t={leadingWhitespace:p.firstChild.nodeType===3,tbody:!p.getElementsByTagName("tbody").length,htmlSerialize:!!p.getElementsByTagName("link").length,style:/top/.test(r.getAttribute("style")),hrefNormalized:r.getAttribute("href")==="/a",opacity:/^0.5/.test
 (r.style.opacity),cssFloat:!!r.style.cssFloat,checkOn:u.value==="on",optSelected:o.selected,getSetAttribute:p.className!=="t",enctype:!!i.createElement("form").enctype,html5Clone:i.createElement("nav").cloneNode(!0).outerHTML!=="<:nav></:nav>",boxModel:i.compatMode==="CSS1Compat",submitBubbles:!0,changeBubbles:!0,focusinBubbles:!1,deleteExpando:!0,noCloneEvent:!0,inlineBlockNeedsLayout:!1,shrinkWrapBlocks:!1,reliableMarginRight:!0,boxSizingReliable:!0,pixelPosition:!1},u.checked=!0,t.noCloneChecked=u.cloneNode(!0).checked,s.disabled=!0,t.optDisabled=!o.disabled;try{delete p.test}catch(d){t.deleteExpando=!1}!p.addEventListener&&p.attachEvent&&p.fireEvent&&(p.attachEvent("onclick",h=function(){t.noCloneEvent=!1}),p.cloneNode(!0).fireEvent("onclick"),p.detachEvent("onclick",h)),u=i.createElement("input"),u.value="t",u.setAttribute("type","radio"),t.radioValue=u.value==="t",u.setAttribute("checked","checked"),u.setAttribute("name","t"),p.appendChild(u),a=i.createDocumentFragment(),a.app
 endChild(p.lastChild),t.checkClone=a.cloneNode(!0).cloneNode(!0).lastChild.checked,t.appendChecked=u.checked,a.removeChild(u),a.appendChild(p);if(p.attachEvent)for(l in{submit:!0,change:!0,focusin:!0})f="on"+l,c=f in p,c||(p.setAttribute(f,"return;"),c=typeof p[f]=="function"),t[l+"Bubbles"]=c;return v(function(){var n,r,s,o,u="padding:0;margin:0;border:0;display:block;overflow:hidden;",a=i.getElementsByTagName("body")[0];if(!a)return;n=i.createElement("div"),n.style.cssText="visibility:hidden;border:0;width:0;height:0;position:static;top:0;margin-top:1px",a.insertBefore(n,a.firstChild),r=i.createElement("div"),n.appendChild(r),r.innerHTML="<table><tr><td></td><td>t</td></tr></table>",s=r.getElementsByTagName("td"),s[0].style.cssText="padding:0;margin:0;border:0;display:none",c=s[0].offsetHeight===0,s[0].style.display="",s[1].style.display="none",t.reliableHiddenOffsets=c&&s[0].offsetHeight===0,r.innerHTML="",r.style.cssText="box-sizing:border-box;-moz-box-sizing:border-box;-webkit-
 box-sizing:border-box;padding:1px;border:1px;display:block;width:4px;margin-top:1%;position:absolute;top:1%;",t.boxSizing=r.offsetWidth===4,t.doesNotIncludeMarginInBodyOffset=a.offsetTop!==1,e.getComputedStyle&&(t.pixelPosition=(e.getComputedStyle(r,null)||{}).top!=="1%",t.boxSizingReliable=(e.getComputedStyle(r,null)||{width:"4px"}).width==="4px",o=i.createElement("div"),o.style.cssText=r.style.cssText=u,o.style.marginRight=o.style.width="0",r.style.width="1px",r.appendChild(o),t.reliableMarginRight=!parseFloat((e.getComputedStyle(o,null)||{}).marginRight)),typeof r.style.zoom!="undefined"&&(r.innerHTML="",r.style.cssText=u+"width:1px;padding:1px;display:inline;zoom:1",t.inlineBlockNeedsLayout=r.offsetWidth===3,r.style.display="block",r.style.overflow="visible",r.innerHTML="<div></div>",r.firstChild.style.width="5px",t.shrinkWrapBlocks=r.offsetWidth!==3,n.style.zoom=1),a.removeChild(n),n=r=s=o=null}),a.removeChild(p),n=r=s=o=u=a=p=null,t}();var D=/(?:\{[\s\S]*\}|\[[\s\S]*\])$/,P=/(
 [A-Z])/g;v.extend({cache:{},deletedIds:[],uuid:0,expando:"jQuery"+(v.fn.jquery+Math.random()).replace(/\D/g,""),noData:{embed:!0,object:"clsid:D27CDB6E-AE6D-11cf-96B8-444553540000",applet:!0},hasData:function(e){return e=e.nodeType?v.cache[e[v.expando]]:e[v.expando],!!e&&!B(e)},data:function(e,n,r,i){if(!v.acceptData(e))return;var s,o,u=v.expando,a=typeof n=="string",f=e.nodeType,l=f?v.cache:e,c=f?e[u]:e[u]&&u;if((!c||!l[c]||!i&&!l[c].data)&&a&&r===t)return;c||(f?e[u]=c=v.deletedIds.pop()||v.guid++:c=u),l[c]||(l[c]={},f||(l[c].toJSON=v.noop));if(typeof n=="object"||typeof n=="function")i?l[c]=v.extend(l[c],n):l[c].data=v.extend(l[c].data,n);return s=l[c],i||(s.data||(s.data={}),s=s.data),r!==t&&(s[v.camelCase(n)]=r),a?(o=s[n],o==null&&(o=s[v.camelCase(n)])):o=s,o},removeData:function(e,t,n){if(!v.acceptData(e))return;var r,i,s,o=e.nodeType,u=o?v.cache:e,a=o?e[v.expando]:v.expando;if(!u[a])return;if(t){r=n?u[a]:u[a].data;if(r){v.isArray(t)||(t in r?t=[t]:(t=v.camelCase(t),t in r?t=[t
 ]:t=t.split(" ")));for(i=0,s=t.length;i<s;i++)delete r[t[i]];if(!(n?B:v.isEmptyObject)(r))return}}if(!n){delete u[a].data;if(!B(u[a]))return}o?v.cleanData([e],!0):v.support.deleteExpando||u!=u.window?delete u[a]:u[a]=null},_data:function(e,t,n){return v.data(e,t,n,!0)},acceptData:function(e){var t=e.nodeName&&v.noData[e.nodeName.toLowerCase()];return!t||t!==!0&&e.getAttribute("classid")===t}}),v.fn.extend({data:function(e,n){var r,i,s,o,u,a=this[0],f=0,l=null;if(e===t){if(this.length){l=v.data(a);if(a.nodeType===1&&!v._data(a,"parsedAttrs")){s=a.attributes;for(u=s.length;f<u;f++)o=s[f].name,o.indexOf("data-")||(o=v.camelCase(o.substring(5)),H(a,o,l[o]));v._data(a,"parsedAttrs",!0)}}return l}return typeof e=="object"?this.each(function(){v.data(this,e)}):(r=e.split(".",2),r[1]=r[1]?"."+r[1]:"",i=r[1]+"!",v.access(this,function(n){if(n===t)return l=this.triggerHandler("getData"+i,[r[0]]),l===t&&a&&(l=v.data(a,e),l=H(a,e,l)),l===t&&r[1]?this.data(r[0]):l;r[1]=n,this.each(function(){var
  t=v(this);t.triggerHandler("setData"+i,r),v.data(this,e,n),t.triggerHandler("changeData"+i,r)})},null,n,arguments.length>1,null,!1))},removeData:function(e){return this.each(function(){v.removeData(this,e)})}}),v.extend({queue:function(e,t,n){var r;if(e)return t=(t||"fx")+"queue",r=v._data(e,t),n&&(!r||v.isArray(n)?r=v._data(e,t,v.makeArray(n)):r.push(n)),r||[]},dequeue:function(e,t){t=t||"fx";var n=v.queue(e,t),r=n.length,i=n.shift(),s=v._queueHooks(e,t),o=function(){v.dequeue(e,t)};i==="inprogress"&&(i=n.shift(),r--),i&&(t==="fx"&&n.unshift("inprogress"),delete s.stop,i.call(e,o,s)),!r&&s&&s.empty.fire()},_queueHooks:function(e,t){var n=t+"queueHooks";return v._data(e,n)||v._data(e,n,{empty:v.Callbacks("once memory").add(function(){v.removeData(e,t+"queue",!0),v.removeData(e,n,!0)})})}}),v.fn.extend({queue:function(e,n){var r=2;return typeof e!="string"&&(n=e,e="fx",r--),arguments.length<r?v.queue(this[0],e):n===t?this:this.each(function(){var t=v.queue(this,e,n);v._queueHooks(th
 is,e),e==="fx"&&t[0]!=="inprogress"&&v.dequeue(this,e)})},dequeue:function(e){return this.each(function(){v.dequeue(this,e)})},delay:function(e,t){return e=v.fx?v.fx.speeds[e]||e:e,t=t||"fx",this.queue(t,function(t,n){var r=setTimeout(t,e);n.stop=function(){clearTimeout(r)}})},clearQueue:function(e){return this.queue(e||"fx",[])},promise:function(e,n){var r,i=1,s=v.Deferred(),o=this,u=this.length,a=function(){--i||s.resolveWith(o,[o])};typeof e!="string"&&(n=e,e=t),e=e||"fx";while(u--)r=v._data(o[u],e+"queueHooks"),r&&r.empty&&(i++,r.empty.add(a));return a(),s.promise(n)}});var j,F,I,q=/[\t\r\n]/g,R=/\r/g,U=/^(?:button|input)$/i,z=/^(?:button|input|object|select|textarea)$/i,W=/^a(?:rea|)$/i,X=/^(?:autofocus|autoplay|async|checked|controls|defer|disabled|hidden|loop|multiple|open|readonly|required|scoped|selected)$/i,V=v.support.getSetAttribute;v.fn.extend({attr:function(e,t){return v.access(this,v.attr,e,t,arguments.length>1)},removeAttr:function(e){return this.each(function(){v.re
 moveAttr(this,e)})},prop:function(e,t){return v.access(this,v.prop,e,t,arguments.length>1)},removeProp:function(e){return e=v.propFix[e]||e,this.each(function(){try{this[e]=t,delete this[e]}catch(n){}})},addClass:function(e){var t,n,r,i,s,o,u;if(v.isFunction(e))return this.each(function(t){v(this).addClass(e.call(this,t,this.className))});if(e&&typeof e=="string"){t=e.split(y);for(n=0,r=this.length;n<r;n++){i=this[n];if(i.nodeType===1)if(!i.className&&t.length===1)i.className=e;else{s=" "+i.className+" ";for(o=0,u=t.length;o<u;o++)s.indexOf(" "+t[o]+" ")<0&&(s+=t[o]+" ");i.className=v.trim(s)}}}return this},removeClass:function(e){var n,r,i,s,o,u,a;if(v.isFunction(e))return this.each(function(t){v(this).removeClass(e.call(this,t,this.className))});if(e&&typeof e=="string"||e===t){n=(e||"").split(y);for(u=0,a=this.length;u<a;u++){i=this[u];if(i.nodeType===1&&i.className){r=(" "+i.className+" ").replace(q," ");for(s=0,o=n.length;s<o;s++)while(r.indexOf(" "+n[s]+" ")>=0)r=r.replace(" "
 +n[s]+" "," ");i.className=e?v.trim(r):""}}}return this},toggleClass:function(e,t){var n=typeof e,r=typeof t=="boolean";return v.isFunction(e)?this.each(function(n){v(this).toggleClass(e.call(this,n,this.className,t),t)}):this.each(function(){if(n==="string"){var i,s=0,o=v(this),u=t,a=e.split(y);while(i=a[s++])u=r?u:!o.hasClass(i),o[u?"addClass":"removeClass"](i)}else if(n==="undefined"||n==="boolean")this.className&&v._data(this,"__className__",this.className),this.className=this.className||e===!1?"":v._data(this,"__className__")||""})},hasClass:function(e){var t=" "+e+" ",n=0,r=this.length;for(;n<r;n++)if(this[n].nodeType===1&&(" "+this[n].className+" ").replace(q," ").indexOf(t)>=0)return!0;return!1},val:function(e){var n,r,i,s=this[0];if(!arguments.length){if(s)return n=v.valHooks[s.type]||v.valHooks[s.nodeName.toLowerCase()],n&&"get"in n&&(r=n.get(s,"value"))!==t?r:(r=s.value,typeof r=="string"?r.replace(R,""):r==null?"":r);return}return i=v.isFunction(e),this.each(function(r){
 var s,o=v(this);if(this.nodeType!==1)return;i?s=e.call(this,r,o.val()):s=e,s==null?s="":typeof s=="number"?s+="":v.isArray(s)&&(s=v.map(s,function(e){return e==null?"":e+""})),n=v.valHooks[this.type]||v.valHooks[this.nodeName.toLowerCase()];if(!n||!("set"in n)||n.set(this,s,"value")===t)this.value=s})}}),v.extend({valHooks:{option:{get:function(e){var t=e.attributes.value;return!t||t.specified?e.value:e.text}},select:{get:function(e){var t,n,r=e.options,i=e.selectedIndex,s=e.type==="select-one"||i<0,o=s?null:[],u=s?i+1:r.length,a=i<0?u:s?i:0;for(;a<u;a++){n=r[a];if((n.selected||a===i)&&(v.support.optDisabled?!n.disabled:n.getAttribute("disabled")===null)&&(!n.parentNode.disabled||!v.nodeName(n.parentNode,"optgroup"))){t=v(n).val();if(s)return t;o.push(t)}}return o},set:function(e,t){var n=v.makeArray(t);return v(e).find("option").each(function(){this.selected=v.inArray(v(this).val(),n)>=0}),n.length||(e.selectedIndex=-1),n}}},attrFn:{},attr:function(e,n,r,i){var s,o,u,a=e.nodeType;i
 f(!e||a===3||a===8||a===2)return;if(i&&v.isFunction(v.fn[n]))return v(e)[n](r);if(typeof e.getAttribute=="undefined")return v.prop(e,n,r);u=a!==1||!v.isXMLDoc(e),u&&(n=n.toLowerCase(),o=v.attrHooks[n]||(X.test(n)?F:j));if(r!==t){if(r===null){v.removeAttr(e,n);return}return o&&"set"in o&&u&&(s=o.set(e,r,n))!==t?s:(e.setAttribute(n,r+""),r)}return o&&"get"in o&&u&&(s=o.get(e,n))!==null?s:(s=e.getAttribute(n),s===null?t:s)},removeAttr:function(e,t){var n,r,i,s,o=0;if(t&&e.nodeType===1){r=t.split(y);for(;o<r.length;o++)i=r[o],i&&(n=v.propFix[i]||i,s=X.test(i),s||v.attr(e,i,""),e.removeAttribute(V?i:n),s&&n in e&&(e[n]=!1))}},attrHooks:{type:{set:function(e,t){if(U.test(e.nodeName)&&e.parentNode)v.error("type property can't be changed");else if(!v.support.radioValue&&t==="radio"&&v.nodeName(e,"input")){var n=e.value;return e.setAttribute("type",t),n&&(e.value=n),t}}},value:{get:function(e,t){return j&&v.nodeName(e,"button")?j.get(e,t):t in e?e.value:null},set:function(e,t,n){if(j&&v.node
 Name(e,"button"))return j.set(e,t,n);e.value=t}}},propFix:{tabindex:"tabIndex",readonly:"readOnly","for":"htmlFor","class":"className",maxlength:"maxLength",cellspacing:"cellSpacing",cellpadding:"cellPadding",rowspan:"rowSpan",colspan:"colSpan",usemap:"useMap",frameborder:"frameBorder",contenteditable:"contentEditable"},prop:function(e,n,r){var i,s,o,u=e.nodeType;if(!e||u===3||u===8||u===2)return;return o=u!==1||!v.isXMLDoc(e),o&&(n=v.propFix[n]||n,s=v.propHooks[n]),r!==t?s&&"set"in s&&(i=s.set(e,r,n))!==t?i:e[n]=r:s&&"get"in s&&(i=s.get(e,n))!==null?i:e[n]},propHooks:{tabIndex:{get:function(e){var n=e.getAttributeNode("tabindex");return n&&n.specified?parseInt(n.value,10):z.test(e.nodeName)||W.test(e.nodeName)&&e.href?0:t}}}}),F={get:function(e,n){var r,i=v.prop(e,n);return i===!0||typeof i!="boolean"&&(r=e.getAttributeNode(n))&&r.nodeValue!==!1?n.toLowerCase():t},set:function(e,t,n){var r;return t===!1?v.removeAttr(e,n):(r=v.propFix[n]||n,r in e&&(e[r]=!0),e.setAttribute(n,n.toLow
 erCase())),n}},V||(I={name:!0,id:!0,coords:!0},j=v.valHooks.button={get:function(e,n){var r;return r=e.getAttributeNode(n),r&&(I[n]?r.value!=="":r.specified)?r.value:t},set:function(e,t,n){var r=e.getAttributeNode(n);return r||(r=i.createAttribute(n),e.setAttributeNode(r)),r.value=t+""}},v.each(["width","height"],function(e,t){v.attrHooks[t]=v.extend(v.attrHooks[t],{set:function(e,n){if(n==="")return e.setAttribute(t,"auto"),n}})}),v.attrHooks.contenteditable={get:j.get,set:function(e,t,n){t===""&&(t="false"),j.set(e,t,n)}}),v.support.hrefNormalized||v.each(["href","src","width","height"],function(e,n){v.attrHooks[n]=v.extend(v.attrHooks[n],{get:function(e){var r=e.getAttribute(n,2);return r===null?t:r}})}),v.support.style||(v.attrHooks.style={get:function(e){return e.style.cssText.toLowerCase()||t},set:function(e,t){return e.style.cssText=t+""}}),v.support.optSelected||(v.propHooks.selected=v.extend(v.propHooks.selected,{get:function(e){var t=e.parentNode;return t&&(t.selectedIndex
 ,t.parentNode&&t.parentNode.selectedIndex),null}})),v.support.enctype||(v.propFix.enctype="encoding"),v.support.checkOn||v.each(["radio","checkbox"],function(){v.valHooks[this]={get:function(e){return e.getAttribute("value")===null?"on":e.value}}}),v.each(["radio","checkbox"],function(){v.valHooks[this]=v.extend(v.valHooks[this],{set:function(e,t){if(v.isArray(t))return e.checked=v.inArray(v(e).val(),t)>=0}})});var $=/^(?:textarea|input|select)$/i,J=/^([^\.]*|)(?:\.(.+)|)$/,K=/(?:^|\s)hover(\.\S+|)\b/,Q=/^key/,G=/^(?:mouse|contextmenu)|click/,Y=/^(?:focusinfocus|focusoutblur)$/,Z=function(e){return v.event.special.hover?e:e.replace(K,"mouseenter$1 mouseleave$1")};v.event={add:function(e,n,r,i,s){var o,u,a,f,l,c,h,p,d,m,g;if(e.nodeType===3||e.nodeType===8||!n||!r||!(o=v._data(e)))return;r.handler&&(d=r,r=d.handler,s=d.selector),r.guid||(r.guid=v.guid++),a=o.events,a||(o.events=a={}),u=o.handle,u||(o.handle=u=function(e){return typeof v=="undefined"||!!e&&v.event.triggered===e.type?t:
 v.event.dispatch.apply(u.elem,arguments)},u.elem=e),n=v.trim(Z(n)).split(" ");for(f=0;f<n.length;f++){l=J.exec(n[f])||[],c=l[1],h=(l[2]||"").split(".").sort(),g=v.event.special[c]||{},c=(s?g.delegateType:g.bindType)||c,g=v.event.special[c]||{},p=v.extend({type:c,origType:l[1],data:i,handler:r,guid:r.guid,selector:s,needsContext:s&&v.expr.match.needsContext.test(s),namespace:h.join(".")},d),m=a[c];if(!m){m=a[c]=[],m.delegateCount=0;if(!g.setup||g.setup.call(e,i,h,u)===!1)e.addEventListener?e.addEventListener(c,u,!1):e.attachEvent&&e.attachEvent("on"+c,u)}g.add&&(g.add.call(e,p),p.handler.guid||(p.handler.guid=r.guid)),s?m.splice(m.delegateCount++,0,p):m.push(p),v.event.global[c]=!0}e=null},global:{},remove:function(e,t,n,r,i){var s,o,u,a,f,l,c,h,p,d,m,g=v.hasData(e)&&v._data(e);if(!g||!(h=g.events))return;t=v.trim(Z(t||"")).split(" ");for(s=0;s<t.length;s++){o=J.exec(t[s])||[],u=a=o[1],f=o[2];if(!u){for(u in h)v.event.remove(e,u+t[s],n,r,!0);continue}p=v.event.special[u]||{},u=(r?p.d
 elegateType:p.bindType)||u,d=h[u]||[],l=d.length,f=f?new RegExp("(^|\\.)"+f.split(".").sort().join("\\.(?:.*\\.|)")+"(\\.|$)"):null;for(c=0;c<d.length;c++)m=d[c],(i||a===m.origType)&&(!n||n.guid===m.guid)&&(!f||f.test(m.namespace))&&(!r||r===m.selector||r==="**"&&m.selector)&&(d.splice(c--,1),m.selector&&d.delegateCount--,p.remove&&p.remove.call(e,m));d.length===0&&l!==d.length&&((!p.teardown||p.teardown.call(e,f,g.handle)===!1)&&v.removeEvent(e,u,g.handle),delete h[u])}v.isEmptyObject(h)&&(delete g.handle,v.removeData(e,"events",!0))},customEvent:{getData:!0,setData:!0,changeData:!0},trigger:function(n,r,s,o){if(!s||s.nodeType!==3&&s.nodeType!==8){var u,a,f,l,c,h,p,d,m,g,y=n.type||n,b=[];if(Y.test(y+v.event.triggered))return;y.indexOf("!")>=0&&(y=y.slice(0,-1),a=!0),y.indexOf(".")>=0&&(b=y.split("."),y=b.shift(),b.sort());if((!s||v.event.customEvent[y])&&!v.event.global[y])return;n=typeof n=="object"?n[v.expando]?n:new v.Event(y,n):new v.Event(y),n.type=y,n.isTrigger=!0,n.exclusive
 =a,n.namespace=b.join("."),n.namespace_re=n.namespace?new RegExp("(^|\\.)"+b.join("\\.(?:.*\\.|)")+"(\\.|$)"):null,h=y.indexOf(":")<0?"on"+y:"";if(!s){u=v.cache;for(f in u)u[f].events&&u[f].events[y]&&v.event.trigger(n,r,u[f].handle.elem,!0);return}n.result=t,n.target||(n.target=s),r=r!=null?v.makeArray(r):[],r.unshift(n),p=v.event.special[y]||{};if(p.trigger&&p.trigger.apply(s,r)===!1)return;m=[[s,p.bindType||y]];if(!o&&!p.noBubble&&!v.isWindow(s)){g=p.delegateType||y,l=Y.test(g+y)?s:s.parentNode;for(c=s;l;l=l.parentNode)m.push([l,g]),c=l;c===(s.ownerDocument||i)&&m.push([c.defaultView||c.parentWindow||e,g])}for(f=0;f<m.length&&!n.isPropagationStopped();f++)l=m[f][0],n.type=m[f][1],d=(v._data(l,"events")||{})[n.type]&&v._data(l,"handle"),d&&d.apply(l,r),d=h&&l[h],d&&v.acceptData(l)&&d.apply&&d.apply(l,r)===!1&&n.preventDefault();return n.type=y,!o&&!n.isDefaultPrevented()&&(!p._default||p._default.apply(s.ownerDocument,r)===!1)&&(y!=="click"||!v.nodeName(s,"a"))&&v.acceptData(s)&&h
 &&s[y]&&(y!=="focus"&&y!=="blur"||n.target.offsetWidth!==0)&&!v.isWindow(s)&&(c=s[h],c&&(s[h]=null),v.event.triggered=y,s[y](),v.event.triggered=t,c&&(s[h]=c)),n.result}return},dispatch:function(n){n=v.event.fix(n||e.event);var r,i,s,o,u,a,f,c,h,p,d=(v._data(this,"events")||{})[n.type]||[],m=d.delegateCount,g=l.call(arguments),y=!n.exclusive&&!n.namespace,b=v.event.special[n.type]||{},w=[];g[0]=n,n.delegateTarget=this;if(b.preDispatch&&b.preDispatch.call(this,n)===!1)return;if(m&&(!n.button||n.type!=="click"))for(s=n.target;s!=this;s=s.parentNode||this)if(s.disabled!==!0||n.type!=="click"){u={},f=[];for(r=0;r<m;r++)c=d[r],h=c.selector,u[h]===t&&(u[h]=c.needsContext?v(h,this).index(s)>=0:v.find(h,this,null,[s]).length),u[h]&&f.push(c);f.length&&w.push({elem:s,matches:f})}d.length>m&&w.push({elem:this,matches:d.slice(m)});for(r=0;r<w.length&&!n.isPropagationStopped();r++){a=w[r],n.currentTarget=a.elem;for(i=0;i<a.matches.length&&!n.isImmediatePropagationStopped();i++){c=a.matches[i];i
 f(y||!n.namespace&&!c.namespace||n.namespace_re&&n.namespace_re.test(c.namespace))n.data=c.data,n.handleObj=c,o=((v.event.special[c.origType]||{}).handle||c.handler).apply(a.elem,g),o!==t&&(n.result=o,o===!1&&(n.preventDefault(),n.stopPropagation()))}}return b.postDispatch&&b.postDispatch.call(this,n),n.result},props:"attrChange attrName relatedNode srcElement altKey bubbles cancelable ctrlKey currentTarget eventPhase metaKey relatedTarget shiftKey target timeStamp view which".split(" "),fixHooks:{},keyHooks:{props:"char charCode key keyCode".split(" "),filter:function(e,t){return e.which==null&&(e.which=t.charCode!=null?t.charCode:t.keyCode),e}},mouseHooks:{props:"button buttons clientX clientY fromElement offsetX offsetY pageX pageY screenX screenY toElement".split(" "),filter:function(e,n){var r,s,o,u=n.button,a=n.fromElement;return e.pageX==null&&n.clientX!=null&&(r=e.target.ownerDocument||i,s=r.documentElement,o=r.body,e.pageX=n.clientX+(s&&s.scrollLeft||o&&o.scrollLeft||0)-(s&
 &s.clientLeft||o&&o.clientLeft||0),e.pageY=n.clientY+(s&&s.scrollTop||o&&o.scrollTop||0)-(s&&s.clientTop||o&&o.clientTop||0)),!e.relatedTarget&&a&&(e.relatedTarget=a===e.target?n.toElement:a),!e.which&&u!==t&&(e.which=u&1?1:u&2?3:u&4?2:0),e}},fix:function(e){if(e[v.expando])return e;var t,n,r=e,s=v.event.fixHooks[e.type]||{},o=s.props?this.props.concat(s.props):this.props;e=v.Event(r);for(t=o.length;t;)n=o[--t],e[n]=r[n];return e.target||(e.target=r.srcElement||i),e.target.nodeType===3&&(e.target=e.target.parentNode),e.metaKey=!!e.metaKey,s.filter?s.filter(e,r):e},special:{load:{noBubble:!0},focus:{delegateType:"focusin"},blur:{delegateType:"focusout"},beforeunload:{setup:function(e,t,n){v.isWindow(this)&&(this.onbeforeunload=n)},teardown:function(e,t){this.onbeforeunload===t&&(this.onbeforeunload=null)}}},simulate:function(e,t,n,r){var i=v.extend(new v.Event,n,{type:e,isSimulated:!0,originalEvent:{}});r?v.event.trigger(i,null,t):v.event.dispatch.call(t,i),i.isDefaultPrevented()&&n.
 preventDefault()}},v.event.handle=v.event.dispatch,v.removeEvent=i.removeEventListener?function(e,t,n){e.removeEventListener&&e.removeEventListener(t,n,!1)}:function(e,t,n){var r="on"+t;e.detachEvent&&(typeof e[r]=="undefined"&&(e[r]=null),e.detachEvent(r,n))},v.Event=function(e,t){if(!(this instanceof v.Event))return new v.Event(e,t);e&&e.type?(this.originalEvent=e,this.type=e.type,this.isDefaultPrevented=e.defaultPrevented||e.returnValue===!1||e.getPreventDefault&&e.getPreventDefault()?tt:et):this.type=e,t&&v.extend(this,t),this.timeStamp=e&&e.timeStamp||v.now(),this[v.expando]=!0},v.Event.prototype={preventDefault:function(){this.isDefaultPrevented=tt;var e=this.originalEvent;if(!e)return;e.preventDefault?e.preventDefault():e.returnValue=!1},stopPropagation:function(){this.isPropagationStopped=tt;var e=this.originalEvent;if(!e)return;e.stopPropagation&&e.stopPropagation(),e.cancelBubble=!0},stopImmediatePropagation:function(){this.isImmediatePropagationStopped=tt,this.stopPropaga
 tion()},isDefaultPrevented:et,isPropagationStopped:et,isImmediatePropagationStopped:et},v.each({mouseenter:"mouseover",mouseleave:"mouseout"},function(e,t){v.event.special[e]={delegateType:t,bindType:t,handle:function(e){var n,r=this,i=e.relatedTarget,s=e.handleObj,o=s.selector;if(!i||i!==r&&!v.contains(r,i))e.type=s.origType,n=s.handler.apply(this,arguments),e.type=t;return n}}}),v.support.submitBubbles||(v.event.special.submit={setup:function(){if(v.nodeName(this,"form"))return!1;v.event.add(this,"click._submit keypress._submit",function(e){var n=e.target,r=v.nodeName(n,"input")||v.nodeName(n,"button")?n.form:t;r&&!v._data(r,"_submit_attached")&&(v.event.add(r,"submit._submit",function(e){e._submit_bubble=!0}),v._data(r,"_submit_attached",!0))})},postDispatch:function(e){e._submit_bubble&&(delete e._submit_bubble,this.parentNode&&!e.isTrigger&&v.event.simulate("submit",this.parentNode,e,!0))},teardown:function(){if(v.nodeName(this,"form"))return!1;v.event.remove(this,"._submit")}}
 ),v.support.changeBubbles||(v.event.special.change={setup:function(){if($.test(this.nodeName)){if(this.type==="checkbox"||this.type==="radio")v.event.add(this,"propertychange._change",function(e){e.originalEvent.propertyName==="checked"&&(this._just_changed=!0)}),v.event.add(this,"click._change",function(e){this._just_changed&&!e.isTrigger&&(this._just_changed=!1),v.event.simulate("change",this,e,!0)});return!1}v.event.add(this,"beforeactivate._change",function(e){var t=e.target;$.test(t.nodeName)&&!v._data(t,"_change_attached")&&(v.event.add(t,"change._change",function(e){this.parentNode&&!e.isSimulated&&!e.isTrigger&&v.event.simulate("change",this.parentNode,e,!0)}),v._data(t,"_change_attached",!0))})},handle:function(e){var t=e.target;if(this!==t||e.isSimulated||e.isTrigger||t.type!=="radio"&&t.type!=="checkbox")return e.handleObj.handler.apply(this,arguments)},teardown:function(){return v.event.remove(this,"._change"),!$.test(this.nodeName)}}),v.support.focusinBubbles||v.each({f
 ocus:"focusin",blur:"focusout"},function(e,t){var n=0,r=function(e){v.event.simulate(t,e.target,v.event.fix(e),!0)};v.event.special[t]={setup:function(){n++===0&&i.addEventListener(e,r,!0)},teardown:function(){--n===0&&i.removeEventListener(e,r,!0)}}}),v.fn.extend({on:function(e,n,r,i,s){var o,u;if(typeof e=="object"){typeof n!="string"&&(r=r||n,n=t);for(u in e)this.on(u,n,r,e[u],s);return this}r==null&&i==null?(i=n,r=n=t):i==null&&(typeof n=="string"?(i=r,r=t):(i=r,r=n,n=t));if(i===!1)i=et;else if(!i)return this;return s===1&&(o=i,i=function(e){return v().off(e),o.apply(this,arguments)},i.guid=o.guid||(o.guid=v.guid++)),this.each(function(){v.event.add(this,e,i,r,n)})},one:function(e,t,n,r){return this.on(e,t,n,r,1)},off:function(e,n,r){var i,s;if(e&&e.preventDefault&&e.handleObj)return i=e.handleObj,v(e.delegateTarget).off(i.namespace?i.origType+"."+i.namespace:i.origType,i.selector,i.handler),this;if(typeof e=="object"){for(s in e)this.off(s,n,e[s]);return this}if(n===!1||typeof 
 n=="function")r=n,n=t;return r===!1&&(r=et),this.each(function(){v.event.remove(this,e,r,n)})},bind:function(e,t,n){return this.on(e,null,t,n)},unbind:function(e,t){return this.off(e,null,t)},live:function(e,t,n){return v(this.context).on(e,this.selector,t,n),this},die:function(e,t){return v(this.context).off(e,this.selector||"**",t),this},delegate:function(e,t,n,r){return this.on(t,e,n,r)},undelegate:function(e,t,n){return arguments.length===1?this.off(e,"**"):this.off(t,e||"**",n)},trigger:function(e,t){return this.each(function(){v.event.trigger(e,t,this)})},triggerHandler:function(e,t){if(this[0])return v.event.trigger(e,t,this[0],!0)},toggle:function(e){var t=arguments,n=e.guid||v.guid++,r=0,i=function(n){var i=(v._data(this,"lastToggle"+e.guid)||0)%r;return v._data(this,"lastToggle"+e.guid,i+1),n.preventDefault(),t[i].apply(this,arguments)||!1};i.guid=n;while(r<t.length)t[r++].guid=n;return this.click(i)},hover:function(e,t){return this.mouseenter(e).mouseleave(t||e)}}),v.each
 ("blur focus focusin focusout load resize scroll unload click dblclick mousedown mouseup mousemove mouseover mouseout mouseenter mouseleave change select submit keydown keypress keyup error contextmenu".split(" "),function(e,t){v.fn[t]=function(e,n){return n==null&&(n=e,e=null),arguments.length>0?this.on(t,null,e,n):this.trigger(t)},Q.test(t)&&(v.event.fixHooks[t]=v.event.keyHooks),G.test(t)&&(v.event.fixHooks[t]=v.event.mouseHooks)}),function(e,t){function nt(e,t,n,r){n=n||[],t=t||g;var i,s,a,f,l=t.nodeType;if(!e||typeof e!="string")return n;if(l!==1&&l!==9)return[];a=o(t);if(!a&&!r)if(i=R.exec(e))if(f=i[1]){if(l===9){s=t.getElementById(f);if(!s||!s.parentNode)return n;if(s.id===f)return n.push(s),n}else if(t.ownerDocument&&(s=t.ownerDocument.getElementById(f))&&u(t,s)&&s.id===f)return n.push(s),n}else{if(i[2])return S.apply(n,x.call(t.getElementsByTagName(e),0)),n;if((f=i[3])&&Z&&t.getElementsByClassName)return S.apply(n,x.call(t.getElementsByClassName(f),0)),n}return vt(e.replace
 (j,"$1"),t,n,r,a)}function rt(e){return function(t){var n=t.nodeName.toLowerCase();return n==="input"&&t.type===e}}function it(e){return function(t){var n=t.nodeName.toLowerCase();return(n==="input"||n==="button")&&t.type===e}}function st(e){return N(function(t){return t=+t,N(function(n,r){var i,s=e([],n.length,t),o=s.length;while(o--)n[i=s[o]]&&(n[i]=!(r[i]=n[i]))})})}function ot(e,t,n){if(e===t)return n;var r=e.nextSibling;while(r){if(r===t)return-1;r=r.nextSibling}return 1}function ut(e,t){var n,r,s,o,u,a,f,l=L[d][e+" "];if(l)return t?0:l.slice(0);u=e,a=[],f=i.preFilter;while(u){if(!n||(r=F.exec(u)))r&&(u=u.slice(r[0].length)||u),a.push(s=[]);n=!1;if(r=I.exec(u))s.push(n=new m(r.shift())),u=u.slice(n.length),n.type=r[0].replace(j," ");for(o in i.filter)(r=J[o].exec(u))&&(!f[o]||(r=f[o](r)))&&(s.push(n=new m(r.shift())),u=u.slice(n.length),n.type=o,n.matches=r);if(!n)break}return t?u.length:u?nt.error(e):L(e,a).slice(0)}function at(e,t,r){var i=t.dir,s=r&&t.dir==="parentNode",o=w+
 +;return t.first?function(t,n,r){while(t=t[i])if(s||t.nodeType===1)return e(t,n,r)}:function(t,r,u){if(!u){var a,f=b+" "+o+" ",l=f+n;while(t=t[i])if(s||t.nodeType===1){if((a=t[d])===l)return t.sizset;if(typeof a=="string"&&a.indexOf(f)===0){if(t.sizset)return t}else{t[d]=l;if(e(t,r,u))return t.sizset=!0,t;t.sizset=!1}}}else while(t=t[i])if(s||t.nodeType===1)if(e(t,r,u))return t}}function ft(e){return e.length>1?function(t,n,r){var i=e.length;while(i--)if(!e[i](t,n,r))return!1;return!0}:e[0]}function lt(e,t,n,r,i){var s,o=[],u=0,a=e.length,f=t!=null;for(;u<a;u++)if(s=e[u])if(!n||n(s,r,i))o.push(s),f&&t.push(u);return o}function ct(e,t,n,r,i,s){return r&&!r[d]&&(r=ct(r)),i&&!i[d]&&(i=ct(i,s)),N(function(s,o,u,a){var f,l,c,h=[],p=[],d=o.length,v=s||dt(t||"*",u.nodeType?[u]:u,[]),m=e&&(s||!t)?lt(v,h,e,u,a):v,g=n?i||(s?e:d||r)?[]:o:m;n&&n(m,g,u,a);if(r){f=lt(g,p),r(f,[],u,a),l=f.length;while(l--)if(c=f[l])g[p[l]]=!(m[p[l]]=c)}if(s){if(i||e){if(i){f=[],l=g.length;while(l--)(c=g[l])&&f.pus
 h(m[l]=c);i(null,g=[],f,a)}l=g.length;while(l--)(c=g[l])&&(f=i?T.call(s,c):h[l])>-1&&(s[f]=!(o[f]=c))}}else g=lt(g===o?g.splice(d,g.length):g),i?i(null,o,g,a):S.apply(o,g)})}function ht(e){var t,n,r,s=e.length,o=i.relative[e[0].type],u=o||i.relative[" "],a=o?1:0,f=at(function(e){return e===t},u,!0),l=at(function(e){return T.call(t,e)>-1},u,!0),h=[function(e,n,r){return!o&&(r||n!==c)||((t=n).nodeType?f(e,n,r):l(e,n,r))}];for(;a<s;a++)if(n=i.relative[e[a].type])h=[at(ft(h),n)];else{n=i.filter[e[a].type].apply(null,e[a].matches);if(n[d]){r=++a;for(;r<s;r++)if(i.relative[e[r].type])break;return ct(a>1&&ft(h),a>1&&e.slice(0,a-1).join("").replace(j,"$1"),n,a<r&&ht(e.slice(a,r)),r<s&&ht(e=e.slice(r)),r<s&&e.join(""))}h.push(n)}return ft(h)}function pt(e,t){var r=t.length>0,s=e.length>0,o=function(u,a,f,l,h){var p,d,v,m=[],y=0,w="0",x=u&&[],T=h!=null,N=c,C=u||s&&i.find.TAG("*",h&&a.parentNode||a),k=b+=N==null?1:Math.E;T&&(c=a!==g&&a,n=o.el);for(;(p=C[w])!=null;w++){if(s&&p){for(d=0;v=e[d];d
 ++)if(v(p,a,f)){l.push(p);break}T&&(b=k,n=++o.el)}r&&((p=!v&&p)&&y--,u&&x.push(p))}y+=w;if(r&&w!==y){for(d=0;v=t[d];d++)v(x,m,a,f);if(u){if(y>0)while(w--)!x[w]&&!m[w]&&(m[w]=E.call(l));m=lt(m)}S.apply(l,m),T&&!u&&m.length>0&&y+t.length>1&&nt.uniqueSort(l)}return T&&(b=k,c=N),x};return o.el=0,r?N(o):o}function dt(e,t,n){var r=0,i=t.length;for(;r<i;r++)nt(e,t[r],n);return n}function vt(e,t,n,r,s){var o,u,f,l,c,h=ut(e),p=h.length;if(!r&&h.length===1){u=h[0]=h[0].slice(0);if(u.length>2&&(f=u[0]).type==="ID"&&t.nodeType===9&&!s&&i.relative[u[1].type]){t=i.find.ID(f.matches[0].replace($,""),t,s)[0];if(!t)return n;e=e.slice(u.shift().length)}for(o=J.POS.test(e)?-1:u.length-1;o>=0;o--){f=u[o];if(i.relative[l=f.type])break;if(c=i.find[l])if(r=c(f.matches[0].replace($,""),z.test(u[0].type)&&t.parentNode||t,s)){u.splice(o,1),e=r.length&&u.join("");if(!e)return S.apply(n,x.call(r,0)),n;break}}}return a(e,h)(r,t,s,n,z.test(e)),n}function mt(){}var n,r,i,s,o,u,a,f,l,c,h=!0,p="undefined",d=("sizca
 che"+Math.random()).replace(".",""),m=String,g=e.document,y=g.documentElement,b=0,w=0,E=[].pop,S=[].push,x=[].slice,T=[].indexOf||function(e){var t=0,n=this.length;for(;t<n;t++)if(this[t]===e)return t;return-1},N=function(e,t){return e[d]=t==null||t,e},C=function(){var e={},t=[];return N(function(n,r){return t.push(n)>i.cacheLength&&delete e[t.shift()],e[n+" "]=r},e)},k=C(),L=C(),A=C(),O="[\\x20\\t\\r\\n\\f]",M="(?:\\\\.|[-\\w]|[^\\x00-\\xa0])+",_=M.replace("w","w#"),D="([*^$|!~]?=)",P="\\["+O+"*("+M+")"+O+"*(?:"+D+O+"*(?:(['\"])((?:\\\\.|[^\\\\])*?)\\3|("+_+")|)|)"+O+"*\\]",H=":("+M+")(?:\\((?:(['\"])((?:\\\\.|[^\\\\])*?)\\2|([^()[\\]]*|(?:(?:"+P+")|[^:]|\\\\.)*|.*))\\)|)",B=":(even|odd|eq|gt|lt|nth|first|last)(?:\\("+O+"*((?:-\\d)?\\d*)"+O+"*\\)|)(?=[^-]|$)",j=new RegExp("^"+O+"+|((?:^|[^\\\\])(?:\\\\.)*)"+O+"+$","g"),F=new RegExp("^"+O+"*,"+O+"*"),I=new RegExp("^"+O+"*([\\x20\\t\\r\\n\\f>+~])"+O+"*"),q=new RegExp(H),R=/^(?:#([\w\-]+)|(\w+)|\.([\w\-]+))$/,U=/^:not/,z=/[\x20\t\r\n\
 f]*[+~]/,W=/:not\($/,X=/h\d/i,V=/input|select|textarea|button/i,$=/\\(?!\\)/g,J={ID:new RegExp("^#("+M+")"),CLASS:new RegExp("^\\.("+M+")"),NAME:new RegExp("^\\[name=['\"]?("+M+")['\"]?\\]"),TAG:new RegExp("^("+M.replace("w","w*")+")"),ATTR:new RegExp("^"+P),PSEUDO:new RegExp("^"+H),POS:new RegExp(B,"i"),CHILD:new RegExp("^:(only|nth|first|last)-child(?:\\("+O+"*(even|odd|(([+-]|)(\\d*)n|)"+O+"*(?:([+-]|)"+O+"*(\\d+)|))"+O+"*\\)|)","i"),needsContext:new RegExp("^"+O+"*[>+~]|"+B,"i")},K=function(e){var t=g.createElement("div");try{return e(t)}catch(n){return!1}finally{t=null}},Q=K(function(e){return e.appendChild(g.createComment("")),!e.getElementsByTagName("*").length}),G=K(function(e){return e.innerHTML="<a href='#'></a>",e.firstChild&&typeof e.firstChild.getAttribute!==p&&e.firstChild.getAttribute("href")==="#"}),Y=K(function(e){e.innerHTML="<select></select>";var t=typeof e.lastChild.getAttribute("multiple");return t!=="boolean"&&t!=="string"}),Z=K(function(e){return e.innerHTML=
 "<div class='hidden e'></div><div class='hidden'></div>",!e.getElementsByClassName||!e.getElementsByClassName("e").length?!1:(e.lastChild.className="e",e.getElementsByClassName("e").length===2)}),et=K(function(e){e.id=d+0,e.innerHTML="<a name='"+d+"'></a><div name='"+d+"'></div>",y.insertBefore(e,y.firstChild);var t=g.getElementsByName&&g.getElementsByName(d).length===2+g.getElementsByName(d+0).length;return r=!g.getElementById(d),y.removeChild(e),t});try{x.call(y.childNodes,0)[0].nodeType}catch(tt){x=function(e){var t,n=[];for(;t=this[e];e++)n.push(t);return n}}nt.matches=function(e,t){return nt(e,null,null,t)},nt.matchesSelector=function(e,t){return nt(t,null,null,[e]).length>0},s=nt.getText=function(e){var t,n="",r=0,i=e.nodeType;if(i){if(i===1||i===9||i===11){if(typeof e.textContent=="string")return e.textContent;for(e=e.firstChild;e;e=e.nextSibling)n+=s(e)}else if(i===3||i===4)return e.nodeValue}else for(;t=e[r];r++)n+=s(t);return n},o=nt.isXML=function(e){var t=e&&(e.ownerDocu
 ment||e).documentElement;return t?t.nodeName!=="HTML":!1},u=nt.contains=y.contains?function(e,t){var n=e.nodeType===9?e.documentElement:e,r=t&&t.parentNode;return e===r||!!(r&&r.nodeType===1&&n.contains&&n.contains(r))}:y.compareDocumentPosition?function(e,t){return t&&!!(e.compareDocumentPosition(t)&16)}:function(e,t){while(t=t.parentNode)if(t===e)return!0;return!1},nt.attr=function(e,t){var n,r=o(e);return r||(t=t.toLowerCase()),(n=i.attrHandle[t])?n(e):r||Y?e.getAttribute(t):(n=e.getAttributeNode(t),n?typeof e[t]=="boolean"?e[t]?t:null:n.specified?n.value:null:null)},i=nt.selectors={cacheLength:50,createPseudo:N,match:J,attrHandle:G?{}:{href:function(e){return e.getAttribute("href",2)},type:function(e){return e.getAttribute("type")}},find:{ID:r?function(e,t,n){if(typeof t.getElementById!==p&&!n){var r=t.getElementById(e);return r&&r.parentNode?[r]:[]}}:function(e,n,r){if(typeof n.getElementById!==p&&!r){var i=n.getElementById(e);return i?i.id===e||typeof i.getAttributeNode!==p&&i
 .getAttributeNode("id").value===e?[i]:t:[]}},TAG:Q?function(e,t){if(typeof t.getElementsByTagName!==p)return t.getElementsByTagName(e)}:function(e,t){var n=t.getElementsByTagName(e);if(e==="*"){var r,i=[],s=0;for(;r=n[s];s++)r.nodeType===1&&i.push(r);return i}return n},NAME:et&&function(e,t){if(typeof t.getElementsByName!==p)return t.getElementsByName(name)},CLASS:Z&&function(e,t,n){if(typeof t.getElementsByClassName!==p&&!n)return t.getElementsByClassName(e)}},relative:{">":{dir:"parentNode",first:!0}," ":{dir:"parentNode"},"+":{dir:"previousSibling",first:!0},"~":{dir:"previousSibling"}},preFilter:{ATTR:function(e){return e[1]=e[1].replace($,""),e[3]=(e[4]||e[5]||"").replace($,""),e[2]==="~="&&(e[3]=" "+e[3]+" "),e.slice(0,4)},CHILD:function(e){return e[1]=e[1].toLowerCase(),e[1]==="nth"?(e[2]||nt.error(e[0]),e[3]=+(e[3]?e[4]+(e[5]||1):2*(e[2]==="even"||e[2]==="odd")),e[4]=+(e[6]+e[7]||e[2]==="odd")):e[2]&&nt.error(e[0]),e},PSEUDO:function(e){var t,n;if(J.CHILD.test(e[0]))return n
 ull;if(e[3])e[2]=e[3];else if(t=e[4])q.test(t)&&(n=ut(t,!0))&&(n=t.indexOf(")",t.length-n)-t.length)&&(t=t.slice(0,n),e[0]=e[0].slice(0,n)),e[2]=t;return e.slice(0,3)}},filter:{ID:r?function(e){return e=e.replace($,""),function(t){return t.getAttribute("id")===e}}:function(e){return e=e.replace($,""),function(t){var n=typeof t.getAttributeNode!==p&&t.getAttributeNode("id");return n&&n.value===e}},TAG:function(e){return e==="*"?function(){return!0}:(e=e.replace($,"").toLowerCase(),function(t){return t.nodeName&&t.nodeName.toLowerCase()===e})},CLASS:function(e){var t=k[d][e+" "];return t||(t=new RegExp("(^|"+O+")"+e+"("+O+"|$)"))&&k(e,function(e){return t.test(e.className||typeof e.getAttribute!==p&&e.getAttribute("class")||"")})},ATTR:function(e,t,n){return function(r,i){var s=nt.attr(r,e);return s==null?t==="!=":t?(s+="",t==="="?s===n:t==="!="?s!==n:t==="^="?n&&s.indexOf(n)===0:t==="*="?n&&s.indexOf(n)>-1:t==="$="?n&&s.substr(s.length-n.length)===n:t==="~="?(" "+s+" ").indexOf(n)>-1
 :t==="|="?s===n||s.substr(0,n.length+1)===n+"-":!1):!0}},CHILD:function(e,t,n,r){return e==="nth"?function(e){var t,i,s=e.parentNode;if(n===1&&r===0)return!0;if(s){i=0;for(t=s.firstChild;t;t=t.nextSibling)if(t.nodeType===1){i++;if(e===t)break}}return i-=r,i===n||i%n===0&&i/n>=0}:function(t){var n=t;switch(e){case"only":case"first":while(n=n.previousSibling)if(n.nodeType===1)return!1;if(e==="first")return!0;n=t;case"last":while(n=n.nextSibling)if(n.nodeType===1)return!1;return!0}}},PSEUDO:function(e,t){var n,r=i.pseudos[e]||i.setFilters[e.toLowerCase()]||nt.error("unsupported pseudo: "+e);return r[d]?r(t):r.length>1?(n=[e,e,"",t],i.setFilters.hasOwnProperty(e.toLowerCase())?N(function(e,n){var i,s=r(e,t),o=s.length;while(o--)i=T.call(e,s[o]),e[i]=!(n[i]=s[o])}):function(e){return r(e,0,n)}):r}},pseudos:{not:N(function(e){var t=[],n=[],r=a(e.replace(j,"$1"));return r[d]?N(function(e,t,n,i){var s,o=r(e,null,i,[]),u=e.length;while(u--)if(s=o[u])e[u]=!(t[u]=s)}):function(e,i,s){return t[
 0]=e,r(t,null,s,n),!n.pop()}}),has:N(function(e){return function(t){return nt(e,t).length>0}}),contains:N(function(e){return function(t){return(t.textContent||t.innerText||s(t)).indexOf(e)>-1}}),enabled:function(e){return e.disabled===!1},disabled:function(e){return e.disabled===!0},checked:function(e){var t=e.nodeName.toLowerCase();return t==="input"&&!!e.checked||t==="option"&&!!e.selected},selected:function(e){return e.parentNode&&e.parentNode.selectedIndex,e.selected===!0},parent:function(e){return!i.pseudos.empty(e)},empty:function(e){var t;e=e.firstChild;while(e){if(e.nodeName>"@"||(t=e.nodeType)===3||t===4)return!1;e=e.nextSibling}return!0},header:function(e){return X.test(e.nodeName)},text:function(e){var t,n;return e.nodeName.toLowerCase()==="input"&&(t=e.type)==="text"&&((n=e.getAttribute("type"))==null||n.toLowerCase()===t)},radio:rt("radio"),checkbox:rt("checkbox"),file:rt("file"),password:rt("password"),image:rt("image"),submit:it("submit"),reset:it("reset"),button:func
 tion(e){var t=e.nodeName.toLowerCase();return t==="input"&&e.type==="button"||t==="button"},input:function(e){return V.test(e.nodeName)},focus:function(e){var t=e.ownerDocument;return e===t.activeElement&&(!t.hasFocus||t.hasFocus())&&!!(e.type||e.href||~e.tabIndex)},active:function(e){return e===e.ownerDocument.activeElement},first:st(function(){return[0]}),last:st(function(e,t){return[t-1]}),eq:st(function(e,t,n){return[n<0?n+t:n]}),even:st(function(e,t){for(var n=0;n<t;n+=2)e.push(n);return e}),odd:st(function(e,t){for(var n=1;n<t;n+=2)e.push(n);return e}),lt:st(function(e,t,n){for(var r=n<0?n+t:n;--r>=0;)e.push(r);return e}),gt:st(function(e,t,n){for(var r=n<0?n+t:n;++r<t;)e.push(r);return e})}},f=y.compareDocumentPosition?function(e,t){return e===t?(l=!0,0):(!e.compareDocumentPosition||!t.compareDocumentPosition?e.compareDocumentPosition:e.compareDocumentPosition(t)&4)?-1:1}:function(e,t){if(e===t)return l=!0,0;if(e.sourceIndex&&t.sourceIndex)return e.sourceIndex-t.sourceIndex;v
 ar n,r,i=[],s=[],o=e.parentNode,u=t.parentNode,a=o;if(o===u)return ot(e,t);if(!o)return-1;if(!u)return 1;while(a)i.unshift(a),a=a.parentNode;a=u;while(a)s.unshift(a),a=a.parentNode;n=i.length,r=s.length;for(var f=0;f<n&&f<r;f++)if(i[f]!==s[f])return ot(i[f],s[f]);return f===n?ot(e,s[f],-1):ot(i[f],t,1)},[0,0].sort(f),h=!l,nt.uniqueSort=function(e){var t,n=[],r=1,i=0;l=h,e.sort(f);if(l){for(;t=e[r];r++)t===e[r-1]&&(i=n.push(r));while(i--)e.splice(n[i],1)}return e},nt.error=function(e){throw new Error("Syntax error, unrecognized expression: "+e)},a=nt.compile=function(e,t){var n,r=[],i=[],s=A[d][e+" "];if(!s){t||(t=ut(e)),n=t.length;while(n--)s=ht(t[n]),s[d]?r.push(s):i.push(s);s=A(e,pt(i,r))}return s},g.querySelectorAll&&function(){var e,t=vt,n=/'|\\/g,r=/\=[\x20\t\r\n\f]*([^'"\]]*)[\x20\t\r\n\f]*\]/g,i=[":focus"],s=[":active"],u=y.matchesSelector||y.mozMatchesSelector||y.webkitMatchesSelector||y.oMatchesSelector||y.msMatchesSelector;K(function(e){e.innerHTML="<select><option selecte
 d=''></option></select>",e.querySelectorAll("[selected]").length||i.push("\\["+O+"*(?:checked|disabled|ismap|multiple|readonly|selected|value)"),e.querySelectorAll(":checked").length||i.push(":checked")}),K(function(e){e.innerHTML="<p test=''></p>",e.querySelectorAll("[test^='']").length&&i.push("[*^$]="+O+"*(?:\"\"|'')"),e.innerHTML="<input type='hidden'/>",e.querySelectorAll(":enabled").length||i.push(":enabled",":disabled")}),i=new RegExp(i.join("|")),vt=function(e,r,s,o,u){if(!o&&!u&&!i.test(e)){var a,f,l=!0,c=d,h=r,p=r.nodeType===9&&e;if(r.nodeType===1&&r.nodeName.toLowerCase()!=="object"){a=ut(e),(l=r.getAttribute("id"))?c=l.replace(n,"\\$&"):r.setAttribute("id",c),c="[id='"+c+"'] ",f=a.length;while(f--)a[f]=c+a[f].join("");h=z.test(e)&&r.parentNode||r,p=a.join(",")}if(p)try{return S.apply(s,x.call(h.querySelectorAll(p),0)),s}catch(v){}finally{l||r.removeAttribute("id")}}return t(e,r,s,o,u)},u&&(K(function(t){e=u.call(t,"div");try{u.call(t,"[test!='']:sizzle"),s.push("!=",H)}c
 atch(n){}}),s=new RegExp(s.join("|")),nt.matchesSelector=function(t,n){n=n.replace(r,"='$1']");if(!o(t)&&!s.test(n)&&!i.test(n))try{var a=u.call(t,n);if(a||e||t.document&&t.document.nodeType!==11)return a}catch(f){}return nt(n,null,null,[t]).length>0})}(),i.pseudos.nth=i.pseudos.eq,i.filters=mt.prototype=i.pseudos,i.setFilters=new mt,nt.attr=v.attr,v.find=nt,v.expr=nt.selectors,v.expr[":"]=v.expr.pseudos,v.unique=nt.uniqueSort,v.text=nt.getText,v.isXMLDoc=nt.isXML,v.contains=nt.contains}(e);var nt=/Until$/,rt=/^(?:parents|prev(?:Until|All))/,it=/^.[^:#\[\.,]*$/,st=v.expr.match.needsContext,ot={children:!0,contents:!0,next:!0,prev:!0};v.fn.extend({find:function(e){var t,n,r,i,s,o,u=this;if(typeof e!="string")return v(e).filter(function(){for(t=0,n=u.length;t<n;t++)if(v.contains(u[t],this))return!0});o=this.pushStack("","find",e);for(t=0,n=this.length;t<n;t++){r=o.length,v.find(e,this[t],o);if(t>0)for(i=r;i<o.length;i++)for(s=0;s<r;s++)if(o[s]===o[i]){o.splice(i--,1);break}}return o},
 has:function(e){var t,n=v(e,this),r=n.length;return this.filter(function(){for(t=0;t<r;t++)if(v.contains(this,n[t]))return!0})},not:function(e){return this.pushStack(ft(this,e,!1),"not",e)},filter:function(e){return this.pushStack(ft(this,e,!0),"filter",e)},is:function(e){return!!e&&(typeof e=="string"?st.test(e)?v(e,this.context).index(this[0])>=0:v.filter(e,this).length>0:this.filter(e).length>0)},closest:function(e,t){var n,r=0,i=this.length,s=[],o=st.test(e)||typeof e!="string"?v(e,t||this.context):0;for(;r<i;r++){n=this[r];while(n&&n.ownerDocument&&n!==t&&n.nodeType!==11){if(o?o.index(n)>-1:v.find.matchesSelector(n,e)){s.push(n);break}n=n.parentNode}}return s=s.length>1?v.unique(s):s,this.pushStack(s,"closest",e)},index:function(e){return e?typeof e=="string"?v.inArray(this[0],v(e)):v.inArray(e.jquery?e[0]:e,this):this[0]&&this[0].parentNode?this.prevAll().length:-1},add:function(e,t){var n=typeof e=="string"?v(e,t):v.makeArray(e&&e.nodeType?[e]:e),r=v.merge(this.get(),n);retur
 n this.pushStack(ut(n[0])||ut(r[0])?r:v.unique(r))},addBack:function(e){return this.add(e==null?this.prevObject:this.prevObject.filter(e))}}),v.fn.andSelf=v.fn.addBack,v.each({parent:function(e){var t=e.parentNode;return t&&t.nodeType!==11?t:null},parents:function(e){return v.dir(e,"parentNode")},parentsUntil:function(e,t,n){return v.dir(e,"parentNode",n)},next:function(e){return at(e,"nextSibling")},prev:function(e){return at(e,"previousSibling")},nextAll:function(e){return v.dir(e,"nextSibling")},prevAll:function(e){return v.dir(e,"previousSibling")},nextUntil:function(e,t,n){return v.dir(e,"nextSibling",n)},prevUntil:function(e,t,n){return v.dir(e,"previousSibling",n)},siblings:function(e){return v.sibling((e.parentNode||{}).firstChild,e)},children:function(e){return v.sibling(e.firstChild)},contents:function(e){return v.nodeName(e,"iframe")?e.contentDocument||e.contentWindow.document:v.merge([],e.childNodes)}},function(e,t){v.fn[e]=function(n,r){var i=v.map(this,t,n);return nt.t
 est(e)||(r=n),r&&typeof r=="string"&&(i=v.filter(r,i)),i=this.length>1&&!ot[e]?v.unique(i):i,this.length>1&&rt.test(e)&&(i=i.reverse()),this.pushStack(i,e,l.call(arguments).join(","))}}),v.extend({filter:function(e,t,n){return n&&(e=":not("+e+")"),t.length===1?v.find.matchesSelector(t[0],e)?[t[0]]:[]:v.find.matches(e,t)},dir:function(e,n,r){var i=[],s=e[n];while(s&&s.nodeType!==9&&(r===t||s.nodeType!==1||!v(s).is(r)))s.nodeType===1&&i.push(s),s=s[n];return i},sibling:function(e,t){var n=[];for(;e;e=e.nextSibling)e.nodeType===1&&e!==t&&n.push(e);return n}});var ct="abbr|article|aside|audio|bdi|canvas|data|datalist|details|figcaption|figure|footer|header|hgroup|mark|meter|nav|output|progress|section|summary|time|video",ht=/ jQuery\d+="(?:null|\d+)"/g,pt=/^\s+/,dt=/<(?!area|br|col|embed|hr|img|input|link|meta|param)(([\w:]+)[^>]*)\/>/gi,vt=/<([\w:]+)/,mt=/<tbody/i,gt=/<|&#?\w+;/,yt=/<(?:script|style|link)/i,bt=/<(?:script|object|embed|option|style)/i,wt=new RegExp("<(?:"+ct+")[\\s/>]",
 "i"),Et=/^(?:checkbox|radio)$/,St=/checked\s*(?:[^=]|=\s*.checked.)/i,xt=/\/(java|ecma)script/i,Tt=/^\s*<!(?:\[CDATA\[|\-\-)|[\]\-]{2}>\s*$/g,Nt={option:[1,"<select multiple='multiple'>","</select>"],legend:[1,"<fieldset>","</fieldset>"],thead:[1,"<table>","</table>"],tr:[2,"<table><tbody>","</tbody></table>"],td:[3,"<table><tbody><tr>","</tr></tbody></table>"],col:[2,"<table><tbody></tbody><colgroup>","</colgroup></table>"],area:[1,"<map>","</map>"],_default:[0,"",""]},Ct=lt(i),kt=Ct.appendChild(i.createElement("div"));Nt.optgroup=Nt.option,Nt.tbody=Nt.tfoot=Nt.colgroup=Nt.caption=Nt.thead,Nt.th=Nt.td,v.support.htmlSerialize||(Nt._default=[1,"X<div>","</div>"]),v.fn.extend({text:function(e){return v.access(this,function(e){return e===t?v.text(this):this.empty().append((this[0]&&this[0].ownerDocument||i).createTextNode(e))},null,e,arguments.length)},wrapAll:function(e){if(v.isFunction(e))return this.each(function(t){v(this).wrapAll(e.call(this,t))});if(this[0]){var t=v(e,this[0].own
 erDocument).eq(0).clone(!0);this[0].parentNode&&t.insertBefore(this[0]),t.map(function(){var e=this;while(e.firstChild&&e.firstChild.nodeType===1)e=e.firstChild;return e}).append(this)}return this},wrapInner:function(e){return v.isFunction(e)?this.each(function(t){v(this).wrapInner(e.call(this,t))}):this.each(function(){var t=v(this),n=t.contents();n.length?n.wrapAll(e):t.append(e)})},wrap:function(e){var t=v.isFunction(e);return this.each(function(n){v(this).wrapAll(t?e.call(this,n):e)})},unwrap:function(){return this.parent().each(function(){v.nodeName(this,"body")||v(this).replaceWith(this.childNodes)}).end()},append:function(){return this.domManip(arguments,!0,function(e){(this.nodeType===1||this.nodeType===11)&&this.appendChild(e)})},prepend:function(){return this.domManip(arguments,!0,function(e){(this.nodeType===1||this.nodeType===11)&&this.insertBefore(e,this.firstChild)})},before:function(){if(!ut(this[0]))return this.domManip(arguments,!1,function(e){this.parentNode.insert
 Before(e,this)});if(arguments.length){var e=v.clean(arguments);return this.pushStack(v.merge(e,this),"before",this.selector)}},after:function(){if(!ut(this[0]))return this.domManip(arguments,!1,function(e){this.parentNode.insertBefore(e,this.nextSibling)});if(arguments.length){var e=v.clean(arguments);return this.pushStack(v.merge(this,e),"after",this.selector)}},remove:function(e,t){var n,r=0;for(;(n=this[r])!=null;r++)if(!e||v.filter(e,[n]).length)!t&&n.nodeType===1&&(v.cleanData(n.getElementsByTagName("*")),v.cleanData([n])),n.parentNode&&n.parentNode.removeChild(n);return this},empty:function(){var e,t=0;for(;(e=this[t])!=null;t++){e.nodeType===1&&v.cleanData(e.getElementsByTagName("*"));while(e.firstChild)e.removeChild(e.firstChild)}return this},clone:function(e,t){return e=e==null?!1:e,t=t==null?e:t,this.map(function(){return v.clone(this,e,t)})},html:function(e){return v.access(this,function(e){var n=this[0]||{},r=0,i=this.length;if(e===t)return n.nodeType===1?n.innerHTML.rep
 lace(ht,""):t;if(typeof e=="string"&&!yt.test(e)&&(v.support.htmlSerialize||!wt.test(e))&&(v.support.leadingWhitespace||!pt.test(e))&&!Nt[(vt.exec(e)||["",""])[1].toLowerCase()]){e=e.replace(dt,"<$1></$2>");try{for(;r<i;r++)n=this[r]||{},n.nodeType===1&&(v.cleanData(n.getElementsByTagName("*")),n.innerHTML=e);n=0}catch(s){}}n&&this.empty().append(e)},null,e,arguments.length)},replaceWith:function(e){return ut(this[0])?this.length?this.pushStack(v(v.isFunction(e)?e():e),"replaceWith",e):this:v.isFunction(e)?this.each(function(t){var n=v(this),r=n.html();n.replaceWith(e.call(this,t,r))}):(typeof e!="string"&&(e=v(e).detach()),this.each(function(){var t=this.nextSibling,n=this.parentNode;v(this).remove(),t?v(t).before(e):v(n).append(e)}))},detach:function(e){return this.remove(e,!0)},domManip:function(e,n,r){e=[].concat.apply([],e);var i,s,o,u,a=0,f=e[0],l=[],c=this.length;if(!v.support.checkClone&&c>1&&typeof f=="string"&&St.test(f))return this.each(function(){v(this).domManip(e,n,r)}
 );if(v.isFunction(f))return this.each(function(i){var s=v(this);e[0]=f.call(this,i,n?s.html():t),s.domManip(e,n,r)});if(this[0]){i=v.buildFragment(e,this,l),o=i.fragment,s=o.firstChild,o.childNodes.length===1&&(o=s);if(s){n=n&&v.nodeName(s,"tr");for(u=i.cacheable||c-1;a<c;a++)r.call(n&&v.nodeName(this[a],"table")?Lt(this[a],"tbody"):this[a],a===u?o:v.clone(o,!0,!0))}o=s=null,l.length&&v.each(l,function(e,t){t.src?v.ajax?v.ajax({url:t.src,type:"GET",dataType:"script",async:!1,global:!1,"throws":!0}):v.error("no ajax"):v.globalEval((t.text||t.textContent||t.innerHTML||"").replace(Tt,"")),t.parentNode&&t.parentNode.removeChild(t)})}return this}}),v.buildFragment=function(e,n,r){var s,o,u,a=e[0];return n=n||i,n=!n.nodeType&&n[0]||n,n=n.ownerDocument||n,e.length===1&&typeof a=="string"&&a.length<512&&n===i&&a.charAt(0)==="<"&&!bt.test(a)&&(v.support.checkClone||!St.test(a))&&(v.support.html5Clone||!wt.test(a))&&(o=!0,s=v.fragments[a],u=s!==t),s||(s=n.createDocumentFragment(),v.clean(e,n,
 s,r),o&&(v.fragments[a]=u&&s)),{fragment:s,cacheable:o}},v.fragments={},v.each({appendTo:"append",prependTo:"prepend",insertBefore:"before",insertAfter:"after",replaceAll:"replaceWith"},function(e,t){v.fn[e]=function(n){var r,i=0,s=[],o=v(n),u=o.length,a=this.length===1&&this[0].parentNode;if((a==null||a&&a.nodeType===11&&a.childNodes.length===1)&&u===1)return o[t](this[0]),this;for(;i<u;i++)r=(i>0?this.clone(!0):this).get(),v(o[i])[t](r),s=s.concat(r);return this.pushStack(s,e,o.selector)}}),v.extend({clone:function(e,t,n){var r,i,s,o;v.support.html5Clone||v.isXMLDoc(e)||!wt.test("<"+e.nodeName+">")?o=e.cloneNode(!0):(kt.innerHTML=e.outerHTML,kt.removeChild(o=kt.firstChild));if((!v.support.noCloneEvent||!v.support.noCloneChecked)&&(e.nodeType===1||e.nodeType===11)&&!v.isXMLDoc(e)){Ot(e,o),r=Mt(e),i=Mt(o);for(s=0;r[s];++s)i[s]&&Ot(r[s],i[s])}if(t){At(e,o);if(n){r=Mt(e),i=Mt(o);for(s=0;r[s];++s)At(r[s],i[s])}}return r=i=null,o},clean:function(e,t,n,r){var s,o,u,a,f,l,c,h,p,d,m,g,y=t=
 ==i&&Ct,b=[];if(!t||typeof t.createDocumentFragment=="undefined")t=i;for(s=0;(u=e[s])!=null;s++){typeof u=="number"&&(u+="");if(!u)continue;if(typeof u=="string")if(!gt.test(u))u=t.createTextNode(u);else{y=y||lt(t),c=t.createElement("div"),y.appendChild(c),u=u.replace(dt,"<$1></$2>"),a=(vt.exec(u)||["",""])[1].toLowerCase(),f=Nt[a]||Nt._default,l=f[0],c.innerHTML=f[1]+u+f[2];while(l--)c=c.lastChild;if(!v.support.tbody){h=mt.test(u),p=a==="table"&&!h?c.firstChild&&c.firstChild.childNodes:f[1]==="<table>"&&!h?c.childNodes:[];for(o=p.length-1;o>=0;--o)v.nodeName(p[o],"tbody")&&!p[o].childNodes.length&&p[o].parentNode.removeChild(p[o])}!v.support.leadingWhitespace&&pt.test(u)&&c.insertBefore(t.createTextNode(pt.exec(u)[0]),c.firstChild),u=c.childNodes,c.parentNode.removeChild(c)}u.nodeType?b.push(u):v.merge(b,u)}c&&(u=c=y=null);if(!v.support.appendChecked)for(s=0;(u=b[s])!=null;s++)v.nodeName(u,"input")?_t(u):typeof u.getElementsByTagName!="undefined"&&v.grep(u.getElementsByTagName("inp
 ut"),_t);if(n){m=function(e){if(!e.type||xt.test(e.type))return r?r.push(e.parentNode?e.parentNode.removeChild(e):e):n.appendChild(e)};for(s=0;(u=b[s])!=null;s++)if(!v.nodeName(u,"script")||!m(u))n.appendChild(u),typeof u.getElementsByTagName!="undefined"&&(g=v.grep(v.merge([],u.getElementsByTagName("script")),m),b.splice.apply(b,[s+1,0].concat(g)),s+=g.length)}return b},cleanData:function(e,t){var n,r,i,s,o=0,u=v.expando,a=v.cache,f=v.support.deleteExpando,l=v.event.special;for(;(i=e[o])!=null;o++)if(t||v.acceptData(i)){r=i[u],n=r&&a[r];if(n){if(n.events)for(s in n.events)l[s]?v.event.remove(i,s):v.removeEvent(i,s,n.handle);a[r]&&(delete a[r],f?delete i[u]:i.removeAttribute?i.removeAttribute(u):i[u]=null,v.deletedIds.push(r))}}}}),function(){var e,t;v.uaMatch=function(e){e=e.toLowerCase();var t=/(chrome)[ \/]([\w.]+)/.exec(e)||/(webkit)[ \/]([\w.]+)/.exec(e)||/(opera)(?:.*version|)[ \/]([\w.]+)/.exec(e)||/(msie) ([\w.]+)/.exec(e)||e.indexOf("compatible")<0&&/(mozilla)(?:.*? rv:([\w
 .]+)|)/.exec(e)||[];return{browser:t[1]||"",version:t[2]||"0"}},e=v.uaMatch(o.userAgent),t={},e.browser&&(t[e.browser]=!0,t.version=e.version),t.chrome?t.webkit=!0:t.webkit&&(t.safari=!0),v.browser=t,v.sub=function(){function e(t,n){return new e.fn.init(t,n)}v.extend(!0,e,this),e.superclass=this,e.fn=e.prototype=this(),e.fn.constructor=e,e.sub=this.sub,e.fn.init=function(r,i){return i&&i instanceof v&&!(i instanceof e)&&(i=e(i)),v.fn.init.call(this,r,i,t)},e.fn.init.prototype=e.fn;var t=e(i);return e}}();var Dt,Pt,Ht,Bt=/alpha\([^)]*\)/i,jt=/opacity=([^)]*)/,Ft=/^(top|right|bottom|left)$/,It=/^(none|table(?!-c[ea]).+)/,qt=/^margin/,Rt=new RegExp("^("+m+")(.*)$","i"),Ut=new RegExp("^("+m+")(?!px)[a-z%]+$","i"),zt=new RegExp("^([-+])=("+m+")","i"),Wt={BODY:"block"},Xt={position:"absolute",visibility:"hidden",display:"block"},Vt={letterSpacing:0,fontWeight:400},$t=["Top","Right","Bottom","Left"],Jt=["Webkit","O","Moz","ms"],Kt=v.fn.toggle;v.fn.extend({css:function(e,n){return v.access(
 this,function(e,n,r){return r!==t?v.style(e,n,r):v.css(e,n)},e,n,arguments.length>1)},show:function(){return Yt(this,!0)},hide:function(){return Yt(this)},toggle:function(e,t){var n=typeof e=="boolean";return v.isFunction(e)&&v.isFunction(t)?Kt.apply(this,arguments):this.each(function(){(n?e:Gt(this))?v(this).show():v(this).hide()})}}),v.extend({cssHooks:{opacity:{get:function(e,t){if(t){var n=Dt(e,"opacity");return n===""?"1":n}}}},cssNumber:{fillOpacity:!0,fontWeight:!0,lineHeight:!0,opacity:!0,orphans:!0,widows:!0,zIndex:!0,zoom:!0},cssProps:{"float":v.support.cssFloat?"cssFloat":"styleFloat"},style:function(e,n,r,i){if(!e||e.nodeType===3||e.nodeType===8||!e.style)return;var s,o,u,a=v.camelCase(n),f=e.style;n=v.cssProps[a]||(v.cssProps[a]=Qt(f,a)),u=v.cssHooks[n]||v.cssHooks[a];if(r===t)return u&&"get"in u&&(s=u.get(e,!1,i))!==t?s:f[n];o=typeof r,o==="string"&&(s=zt.exec(r))&&(r=(s[1]+1)*s[2]+parseFloat(v.css(e,n)),o="number");if(r==null||o==="number"&&isNaN(r))return;o==="number
 "&&!v.cssNumber[a]&&(r+="px");if(!u||!("set"in u)||(r=u.set(e,r,i))!==t)try{f[n]=r}catch(l){}},css:function(e,n,r,i){var s,o,u,a=v.camelCase(n);return n=v.cssProps[a]||(v.cssProps[a]=Qt(e.style,a)),u=v.cssHooks[n]||v.cssHooks[a],u&&"get"in u&&(s=u.get(e,!0,i)),s===t&&(s=Dt(e,n)),s==="normal"&&n in Vt&&(s=Vt[n]),r||i!==t?(o=parseFloat(s),r||v.isNumeric(o)?o||0:s):s},swap:function(e,t,n){var r,i,s={};for(i in t)s[i]=e.style[i],e.style[i]=t[i];r=n.call(e);for(i in t)e.style[i]=s[i];return r}}),e.getComputedStyle?Dt=function(t,n){var r,i,s,o,u=e.getComputedStyle(t,null),a=t.style;return u&&(r=u.getPropertyValue(n)||u[n],r===""&&!v.contains(t.ownerDocument,t)&&(r=v.style(t,n)),Ut.test(r)&&qt.test(n)&&(i=a.width,s=a.minWidth,o=a.maxWidth,a.minWidth=a.maxWidth=a.width=r,r=u.width,a.width=i,a.minWidth=s,a.maxWidth=o)),r}:i.documentElement.currentStyle&&(Dt=function(e,t){var n,r,i=e.currentStyle&&e.currentStyle[t],s=e.style;return i==null&&s&&s[t]&&(i=s[t]),Ut.test(i)&&!Ft.test(t)&&(n=s.left
 ,r=e.runtimeStyle&&e.runtimeStyle.left,r&&(e.runtimeStyle.left=e.currentStyle.left),s.left=t==="fontSize"?"1em":i,i=s.pixelLeft+"px",s.left=n,r&&(e.runtimeStyle.left=r)),i===""?"auto":i}),v.each(["height","width"],function(e,t){v.cssHooks[t]={get:function(e,n,r){if(n)return e.offsetWidth===0&&It.test(Dt(e,"display"))?v.swap(e,Xt,function(){return tn(e,t,r)}):tn(e,t,r)},set:function(e,n,r){return Zt(e,n,r?en(e,t,r,v.support.boxSizing&&v.css(e,"boxSizing")==="border-box"):0)}}}),v.support.opacity||(v.cssHooks.opacity={get:function(e,t){return jt.test((t&&e.currentStyle?e.currentStyle.filter:e.style.filter)||"")?.01*parseFloat(RegExp.$1)+"":t?"1":""},set:function(e,t){var n=e.style,r=e.currentStyle,i=v.isNumeric(t)?"alpha(opacity="+t*100+")":"",s=r&&r.filter||n.filter||"";n.zoom=1;if(t>=1&&v.trim(s.replace(Bt,""))===""&&n.removeAttribute){n.removeAttribute("filter");if(r&&!r.filter)return}n.filter=Bt.test(s)?s.replace(Bt,i):s+" "+i}}),v(function(){v.support.reliableMarginRight||(v.cssH
 ooks.marginRight={get:function(e,t){return v.swap(e,{display:"inline-block"},function(){if(t)return Dt(e,"marginRight")})}}),!v.support.pixelPosition&&v.fn.position&&v.each(["top","left"],function(e,t){v.cssHooks[t]={get:function(e,n){if(n){var r=Dt(e,t);return Ut.test(r)?v(e).position()[t]+"px":r}}}})}),v.expr&&v.expr.filters&&(v.expr.filters.hidden=function(e){return e.offsetWidth===0&&e.offsetHeight===0||!v.support.reliableHiddenOffsets&&(e.style&&e.style.display||Dt(e,"display"))==="none"},v.expr.filters.visible=function(e){return!v.expr.filters.hidden(e)}),v.each({margin:"",padding:"",border:"Width"},function(e,t){v.cssHooks[e+t]={expand:function(n){var r,i=typeof n=="string"?n.split(" "):[n],s={};for(r=0;r<4;r++)s[e+$t[r]+t]=i[r]||i[r-2]||i[0];return s}},qt.test(e)||(v.cssHooks[e+t].set=Zt)});var rn=/%20/g,sn=/\[\]$/,on=/\r?\n/g,un=/^(?:color|date|datetime|datetime-local|email|hidden|month|number|password|range|search|tel|text|time|url|week)$/i,an=/^(?:select|textarea)/i;v.fn.
 extend({serialize:function(){return v.param(this.serializeArray())},serializeArray:function(){return this.map(function(){return this.elements?v.makeArray(this.elements):this}).filter(function(){return this.name&&!this.disabled&&(this.checked||an.test(this.nodeName)||un.test(this.type))}).map(function(e,t){var n=v(this).val();return n==null?null:v.isArray(n)?v.map(n,function(e,n){return{name:t.name,value:e.replace(on,"\r\n")}}):{name:t.name,value:n.replace(on,"\r\n")}}).get()}}),v.param=function(e,n){var r,i=[],s=function(e,t){t=v.isFunction(t)?t():t==null?"":t,i[i.length]=encodeURIComponent(e)+"="+encodeURIComponent(t)};n===t&&(n=v.ajaxSettings&&v.ajaxSettings.traditional);if(v.isArray(e)||e.jquery&&!v.isPlainObject(e))v.each(e,function(){s(this.name,this.value)});else for(r in e)fn(r,e[r],n,s);return i.join("&").replace(rn,"+")};var ln,cn,hn=/#.*$/,pn=/^(.*?):[ \t]*([^\r\n]*)\r?$/mg,dn=/^(?:about|app|app\-storage|.+\-extension|file|res|widget):$/,vn=/^(?:GET|HEAD)$/,mn=/^\/\//,gn=/
 \?/,yn=/<script\b[^<]*(?:(?!<\/script>)<[^<]*)*<\/script>/gi,bn=/([?&])_=[^&]*/,wn=/^([\w\+\.\-]+:)(?:\/\/([^\/?#:]*)(?::(\d+)|)|)/,En=v.fn.load,Sn={},xn={},Tn=["*/"]+["*"];try{cn=s.href}catch(Nn){cn=i.createElement("a"),cn.href="",cn=cn.href}ln=wn.exec(cn.toLowerCase())||[],v.fn.load=function(e,n,r){if(typeof e!="string"&&En)return En.apply(this,arguments);if(!this.length)return this;var i,s,o,u=this,a=e.indexOf(" ");return a>=0&&(i=e.slice(a,e.length),e=e.slice(0,a)),v.isFunction(n)?(r=n,n=t):n&&typeof n=="object"&&(s="POST"),v.ajax({url:e,type:s,dataType:"html",data:n,complete:function(e,t){r&&u.each(r,o||[e.responseText,t,e])}}).done(function(e){o=arguments,u.html(i?v("<div>").append(e.replace(yn,"")).find(i):e)}),this},v.each("ajaxStart ajaxStop ajaxComplete ajaxError ajaxSuccess ajaxSend".split(" "),function(e,t){v.fn[t]=function(e){return this.on(t,e)}}),v.each(["get","post"],function(e,n){v[n]=function(e,r,i,s){return v.isFunction(r)&&(s=s||i,i=r,r=t),v.ajax({type:n,url:e,da
 ta:r,success:i,dataType:s})}}),v.extend({getScript:function(e,n){return v.get(e,t,n,"script")},getJSON:function(e,t,n){return v.get(e,t,n,"json")},ajaxSetup:function(e,t){return t?Ln(e,v.ajaxSettings):(t=e,e=v.ajaxSettings),Ln(e,t),e},ajaxSettings:{url:cn,isLocal:dn.test(ln[1]),global:!0,type:"GET",contentType:"application/x-www-form-urlencoded; charset=UTF-8",processData:!0,async:!0,accepts:{xml:"application/xml, text/xml",html:"text/html",text:"text/plain",json:"application/json, text/javascript","*":Tn},contents:{xml:/xml/,html:/html/,json:/json/},responseFields:{xml:"responseXML",text:"responseText"},converters:{"* text":e.String,"text html":!0,"text json":v.parseJSON,"text xml":v.parseXML},flatOptions:{context:!0,url:!0}},ajaxPrefilter:Cn(Sn),ajaxTransport:Cn(xn),ajax:function(e,n){function T(e,n,s,a){var l,y,b,w,S,T=n;if(E===2)return;E=2,u&&clearTimeout(u),o=t,i=a||"",x.readyState=e>0?4:0,s&&(w=An(c,x,s));if(e>=200&&e<300||e===304)c.ifModified&&(S=x.getResponseHeader("Last-Mod
 ified"),S&&(v.lastModified[r]=S),S=x.getResponseHeader("Etag"),S&&(v.etag[r]=S)),e===304?(T="notmodified",l=!0):(l=On(c,w),T=l.state,y=l.data,b=l.error,l=!b);else{b=T;if(!T||e)T="error",e<0&&(e=0)}x.status=e,x.statusText=(n||T)+"",l?d.resolveWith(h,[y,T,x]):d.rejectWith(h,[x,T,b]),x.statusCode(g),g=t,f&&p.trigger("ajax"+(l?"Success":"Error"),[x,c,l?y:b]),m.fireWith(h,[x,T]),f&&(p.trigger("ajaxComplete",[x,c]),--v.active||v.event.trigger("ajaxStop"))}typeof e=="object"&&(n=e,e=t),n=n||{};var r,i,s,o,u,a,f,l,c=v.ajaxSetup({},n),h=c.context||c,p=h!==c&&(h.nodeType||h instanceof v)?v(h):v.event,d=v.Deferred(),m=v.Callbacks("once memory"),g=c.statusCode||{},b={},w={},E=0,S="canceled",x={readyState:0,setRequestHeader:function(e,t){if(!E){var n=e.toLowerCase();e=w[n]=w[n]||e,b[e]=t}return this},getAllResponseHeaders:function(){return E===2?i:null},getResponseHeader:function(e){var n;if(E===2){if(!s){s={};while(n=pn.exec(i))s[n[1].toLowerCase()]=n[2]}n=s[e.toLowerCase()]}return n===t?null:n
 },overrideMimeType:function(e){return E||(c.mimeType=e),this},abort:function(e){return e=e||S,o&&o.abort(e),T(0,e),this}};d.promise(x),x.success=x.done,x.error=x.fail,x.complete=m.add,x.statusCode=function(e){if(e){var t;if(E<2)for(t in e)g[t]=[g[t],e[t]];else t=e[x.status],x.always(t)}return this},c.url=((e||c.url)+"").replace(hn,"").replace(mn,ln[1]+"//"),c.dataTypes=v.trim(c.dataType||"*").toLowerCase().split(y),c.crossDomain==null&&(a=wn.exec(c.url.toLowerCase()),c.crossDomain=!(!a||a[1]===ln[1]&&a[2]===ln[2]&&(a[3]||(a[1]==="http:"?80:443))==(ln[3]||(ln[1]==="http:"?80:443)))),c.data&&c.processData&&typeof c.data!="string"&&(c.data=v.param(c.data,c.traditional)),kn(Sn,c,n,x);if(E===2)return x;f=c.global,c.type=c.type.toUpperCase(),c.hasContent=!vn.test(c.type),f&&v.active++===0&&v.event.trigger("ajaxStart");if(!c.hasContent){c.data&&(c.url+=(gn.test(c.url)?"&":"?")+c.data,delete c.data),r=c.url;if(c.cache===!1){var N=v.now(),C=c.url.replace(bn,"$1_="+N);c.url=C+(C===c.url?(gn.t
 est(c.url)?"&":"?")+"_="+N:"")}}(c.data&&c.hasContent&&c.contentType!==!1||n.contentType)&&x.setRequestHeader("Content-Type",c.contentType),c.ifModified&&(r=r||c.url,v.lastModified[r]&&x.setRequestHeader("If-Modified-Since",v.lastModified[r]),v.etag[r]&&x.setRequestHeader("If-None-Match",v.etag[r])),x.setRequestHeader("Accept",c.dataTypes[0]&&c.accepts[c.dataTypes[0]]?c.accepts[c.dataTypes[0]]+(c.dataTypes[0]!=="*"?", "+Tn+"; q=0.01":""):c.accepts["*"]);for(l in c.headers)x.setRequestHeader(l,c.headers[l]);if(!c.beforeSend||c.beforeSend.call(h,x,c)!==!1&&E!==2){S="abort";for(l in{success:1,error:1,complete:1})x[l](c[l]);o=kn(xn,c,n,x);if(!o)T(-1,"No Transport");else{x.readyState=1,f&&p.trigger("ajaxSend",[x,c]),c.async&&c.timeout>0&&(u=setTimeout(function(){x.abort("timeout")},c.timeout));try{E=1,o.send(b,T)}catch(k){if(!(E<2))throw k;T(-1,k)}}return x}return x.abort()},active:0,lastModified:{},etag:{}});var Mn=[],_n=/\?/,Dn=/(=)\?(?=&|$)|\?\?/,Pn=v.now();v.ajaxSetup({jsonp:"callbac
 k",jsonpCallback:function(){var e=Mn.pop()||v.expando+"_"+Pn++;return this[e]=!0,e}}),v.ajaxPrefilter("json jsonp",function(n,r,i){var s,o,u,a=n.data,f=n.url,l=n.jsonp!==!1,c=l&&Dn.test(f),h=l&&!c&&typeof a=="string"&&!(n.contentType||"").indexOf("application/x-www-form-urlencoded")&&Dn.test(a);if(n.dataTypes[0]==="jsonp"||c||h)return s=n.jsonpCallback=v.isFunction(n.jsonpCallback)?n.jsonpCallback():n.jsonpCallback,o=e[s],c?n.url=f.replace(Dn,"$1"+s):h?n.data=a.replace(Dn,"$1"+s):l&&(n.url+=(_n.test(f)?"&":"?")+n.jsonp+"="+s),n.converters["script json"]=function(){return u||v.error(s+" was not called"),u[0]},n.dataTypes[0]="json",e[s]=function(){u=arguments},i.always(function(){e[s]=o,n[s]&&(n.jsonpCallback=r.jsonpCallback,Mn.push(s)),u&&v.isFunction(o)&&o(u[0]),u=o=t}),"script"}),v.ajaxSetup({accepts:{script:"text/javascript, application/javascript, application/ecmascript, application/x-ecmascript"},contents:{script:/javascript|ecmascript/},converters:{"text script":function(e){ret
 urn v.globalEval(e),e}}}),v.ajaxPrefilter("script",function(e){e.cache===t&&(e.cache=!1),e.crossDomain&&(e.type="GET",e.global=!1)}),v.ajaxTransport("script",function(e){if(e.crossDomain){var n,r=i.head||i.getElementsByTagName("head")[0]||i.documentElement;return{send:function(s,o){n=i.createElement("script"),n.async="async",e.scriptCharset&&(n.charset=e.scriptCharset),n.src=e.url,n.onload=n.onreadystatechange=function(e,i){if(i||!n.readyState||/loaded|complete/.test(n.readyState))n.onload=n.onreadystatechange=null,r&&n.parentNode&&r.removeChild(n),n=t,i||o(200,"success")},r.insertBefore(n,r.firstChild)},abort:function(){n&&n.onload(0,1)}}}});var Hn,Bn=e.ActiveXObject?function(){for(var e in Hn)Hn[e](0,1)}:!1,jn=0;v.ajaxSettings.xhr=e.ActiveXObject?function(){return!this.isLocal&&Fn()||In()}:Fn,function(e){v.extend(v.support,{ajax:!!e,cors:!!e&&"withCredentials"in e})}(v.ajaxSettings.xhr()),v.support.ajax&&v.ajaxTransport(function(n){if(!n.crossDomain||v.support.cors){var r;return{s
 end:function(i,s){var o,u,a=n.xhr();n.username?a.open(n.type,n.url,n.async,n.username,n.password):a.open(n.type,n.url,n.async);if(n.xhrFields)for(u in n.xhrFields)a[u]=n.xhrFields[u];n.mimeType&&a.overrideMimeType&&a.overrideMimeType(n.mimeType),!n.crossDomain&&!i["X-Requested-With"]&&(i["X-Requested-With"]="XMLHttpRequest");try{for(u in i)a.setRequestHeader(u,i[u])}catch(f){}a.send(n.hasContent&&n.data||null),r=function(e,i){var u,f,l,c,h;try{if(r&&(i||a.readyState===4)){r=t,o&&(a.onreadystatechange=v.noop,Bn&&delete Hn[o]);if(i)a.readyState!==4&&a.abort();else{u=a.status,l=a.getAllResponseHeaders(),c={},h=a.responseXML,h&&h.documentElement&&(c.xml=h);try{c.text=a.responseText}catch(p){}try{f=a.statusText}catch(p){f=""}!u&&n.isLocal&&!n.crossDomain?u=c.text?200:404:u===1223&&(u=204)}}}catch(d){i||s(-1,d)}c&&s(u,f,c,l)},n.async?a.readyState===4?setTimeout(r,0):(o=++jn,Bn&&(Hn||(Hn={},v(e).unload(Bn)),Hn[o]=r),a.onreadystatechange=r):r()},abort:function(){r&&r(0,1)}}}});var qn,Rn,Un=
 /^(?:toggle|show|hide)$/,zn=new RegExp("^(?:([-+])=|)("+m+")([a-z%]*)$","i"),Wn=/queueHooks$/,Xn=[Gn],Vn={"*":[function(e,t){var n,r,i=this.createTween(e,t),s=zn.exec(t),o=i.cur(),u=+o||0,a=1,f=20;if(s){n=+s[2],r=s[3]||(v.cssNumber[e]?"":"px");if(r!=="px"&&u){u=v.css(i.elem,e,!0)||n||1;do a=a||".5",u/=a,v.style(i.elem,e,u+r);while(a!==(a=i.cur()/o)&&a!==1&&--f)}i.unit=r,i.start=u,i.end=s[1]?u+(s[1]+1)*n:n}return i}]};v.Animation=v.extend(Kn,{tweener:function(e,t){v.isFunction(e)?(t=e,e=["*"]):e=e.split(" ");var n,r=0,i=e.length;for(;r<i;r++)n=e[r],Vn[n]=Vn[n]||[],Vn[n].unshift(t)},prefilter:function(e,t){t?Xn.unshift(e):Xn.push(e)}}),v.Tween=Yn,Yn.prototype={constructor:Yn,init:function(e,t,n,r,i,s){this.elem=e,this.prop=n,this.easing=i||"swing",this.options=t,this.start=this.now=this.cur(),this.end=r,this.unit=s||(v.cssNumber[n]?"":"px")},cur:function(){var e=Yn.propHooks[this.prop];return e&&e.get?e.get(this):Yn.propHooks._default.get(this)},run:function(e){var t,n=Yn.propHooks[th
 is.prop];return this.options.duration?this.pos=t=v.easing[this.easing](e,this.options.duration*e,0,1,this.options.duration):this.pos=t=e,this.now=(this.end-this.start)*t+this.start,this.options.step&&this.options.step.call(this.elem,this.now,this),n&&n.set?n.set(this):Yn.propHooks._default.set(this),this}},Yn.prototype.init.prototype=Yn.prototype,Yn.propHooks={_default:{get:function(e){var t;return e.elem[e.prop]==null||!!e.elem.style&&e.elem.style[e.prop]!=null?(t=v.css(e.elem,e.prop,!1,""),!t||t==="auto"?0:t):e.elem[e.prop]},set:function(e){v.fx.step[e.prop]?v.fx.step[e.prop](e):e.elem.style&&(e.elem.style[v.cssProps[e.prop]]!=null||v.cssHooks[e.prop])?v.style(e.elem,e.prop,e.now+e.unit):e.elem[e.prop]=e.now}}},Yn.propHooks.scrollTop=Yn.propHooks.scrollLeft={set:function(e){e.elem.nodeType&&e.elem.parentNode&&(e.elem[e.prop]=e.now)}},v.each(["toggle","show","hide"],function(e,t){var n=v.fn[t];v.fn[t]=function(r,i,s){return r==null||typeof r=="boolean"||!e&&v.isFunction(r)&&v.isFun
 ction(i)?n.apply(this,arguments):this.animate(Zn(t,!0),r,i,s)}}),v.fn.extend({fadeTo:function(e,t,n,r){return this.filter(Gt).css("opacity",0).show().end().animate({opacity:t},e,n,r)},animate:function(e,t,n,r){var i=v.isEmptyObject(e),s=v.speed(t,n,r),o=function(){var t=Kn(this,v.extend({},e),s);i&&t.stop(!0)};return i||s.queue===!1?this.each(o):this.queue(s.queue,o)},stop:function(e,n,r){var i=function(e){var t=e.stop;delete e.stop,t(r)};return typeof e!="string"&&(r=n,n=e,e=t),n&&e!==!1&&this.queue(e||"fx",[]),this.each(function(){var t=!0,n=e!=null&&e+"queueHooks",s=v.timers,o=v._data(this);if(n)o[n]&&o[n].stop&&i(o[n]);else for(n in o)o[n]&&o[n].stop&&Wn.test(n)&&i(o[n]);for(n=s.length;n--;)s[n].elem===this&&(e==null||s[n].queue===e)&&(s[n].anim.stop(r),t=!1,s.splice(n,1));(t||!r)&&v.dequeue(this,e)})}}),v.each({slideDown:Zn("show"),slideUp:Zn("hide"),slideToggle:Zn("toggle"),fadeIn:{opacity:"show"},fadeOut:{opacity:"hide"},fadeToggle:{opacity:"toggle"}},function(e,t){v.fn[e]=fu
 nction(e,n,r){return this.animate(t,e,n,r)}}),v.speed=function(e,t,n){var r=e&&typeof e=="object"?v.extend({},e):{complete:n||!n&&t||v.isFunction(e)&&e,duration:e,easing:n&&t||t&&!v.isFunction(t)&&t};r.duration=v.fx.off?0:typeof r.duration=="number"?r.duration:r.duration in v.fx.speeds?v.fx.speeds[r.duration]:v.fx.speeds._default;if(r.queue==null||r.queue===!0)r.queue="fx";return r.old=r.complete,r.complete=function(){v.isFunction(r.old)&&r.old.call(this),r.queue&&v.dequeue(this,r.queue)},r},v.easing={linear:function(e){return e},swing:function(e){return.5-Math.cos(e*Math.PI)/2}},v.timers=[],v.fx=Yn.prototype.init,v.fx.tick=function(){var e,n=v.timers,r=0;qn=v.now();for(;r<n.length;r++)e=n[r],!e()&&n[r]===e&&n.splice(r--,1);n.length||v.fx.stop(),qn=t},v.fx.timer=function(e){e()&&v.timers.push(e)&&!Rn&&(Rn=setInterval(v.fx.tick,v.fx.interval))},v.fx.interval=13,v.fx.stop=function(){clearInterval(Rn),Rn=null},v.fx.speeds={slow:600,fast:200,_default:400},v.fx.step={},v.expr&&v.expr.fil
 ters&&(v.expr.filters.animated=function(e){return v.grep(v.timers,function(t){return e===t.elem}).length});var er=/^(?:body|html)$/i;v.fn.offset=function(e){if(arguments.length)return e===t?this:this.each(function(t){v.offset.setOffset(this,e,t)});var n,r,i,s,o,u,a,f={top:0,left:0},l=this[0],c=l&&l.ownerDocument;if(!c)return;return(r=c.body)===l?v.offset.bodyOffset(l):(n=c.documentElement,v.contains(n,l)?(typeof l.getBoundingClientRect!="undefined"&&(f=l.getBoundingClientRect()),i=tr(c),s=n.clientTop||r.clientTop||0,o=n.clientLeft||r.clientLeft||0,u=i.pageYOffset||n.scrollTop,a=i.pageXOffset||n.scrollLeft,{top:f.top+u-s,left:f.left+a-o}):f)},v.offset={bodyOffset:function(e){var t=e.offsetTop,n=e.offsetLeft;return v.support.doesNotIncludeMarginInBodyOffset&&(t+=parseFloat(v.css(e,"marginTop"))||0,n+=parseFloat(v.css(e,"marginLeft"))||0),{top:t,left:n}},setOffset:function(e,t,n){var r=v.css(e,"position");r==="static"&&(e.style.position="relative");var i=v(e),s=i.offset(),o=v.css(e,"to
 p"),u=v.css(e,"left"),a=(r==="absolute"||r==="fixed")&&v.inArray("auto",[o,u])>-1,f={},l={},c,h;a?(l=i.position(),c=l.top,h=l.left):(c=parseFloat(o)||0,h=parseFloat(u)||0),v.isFunction(t)&&(t=t.call(e,n,s)),t.top!=null&&(f.top=t.top-s.top+c),t.left!=null&&(f.left=t.left-s.left+h),"using"in t?t.using.call(e,f):i.css(f)}},v.fn.extend({position:function(){if(!this[0])return;var e=this[0],t=this.offsetParent(),n=this.offset(),r=er.test(t[0].nodeName)?{top:0,left:0}:t.offset();return n.top-=parseFloat(v.css(e,"marginTop"))||0,n.left-=parseFloat(v.css(e,"marginLeft"))||0,r.top+=parseFloat(v.css(t[0],"borderTopWidth"))||0,r.left+=parseFloat(v.css(t[0],"borderLeftWidth"))||0,{top:n.top-r.top,left:n.left-r.left}},offsetParent:function(){return this.map(function(){var e=this.offsetParent||i.body;while(e&&!er.test(e.nodeName)&&v.css(e,"position")==="static")e=e.offsetParent;return e||i.body})}}),v.each({scrollLeft:"pageXOffset",scrollTop:"pageYOffset"},function(e,n){var r=/Y/.test(n);v.fn[e]=f
 unction(i){return v.access(this,function(e,i,s){var o=tr(e);if(s===t)return o?n in o?o[n]:o.document.documentElement[i]:e[i];o?o.scrollTo(r?v(o).scrollLeft():s,r?s:v(o).scrollTop()):e[i]=s},e,i,arguments.length,null)}}),v.each({Height:"height",Width:"width"},function(e,n){v.each({padding:"inner"+e,content:n,"":"outer"+e},function(r,i){v.fn[i]=function(i,s){var o=arguments.length&&(r||typeof i!="boolean"),u=r||(i===!0||s===!0?"margin":"border");return v.access(this,function(n,r,i){var s;return v.isWindow(n)?n.document.documentElement["client"+e]:n.nodeType===9?(s=n.documentElement,Math.max(n.body["scroll"+e],s["scroll"+e],n.body["offset"+e],s["offset"+e],s["client"+e])):i===t?v.css(n,r,i,u):v.style(n,r,i,u)},n,o?i:t,o,null)}})}),e.jQuery=e.$=v,typeof define=="function"&&define.amd&&define.amd.jQuery&&define("jquery",[],function(){return v})})(window);
\ No newline at end of file

Added: www-releases/trunk/3.9.1/docs/_static/lines.gif
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_static/lines.gif?rev=290368&view=auto
==============================================================================
Binary file - no diff available.

Propchange: www-releases/trunk/3.9.1/docs/_static/lines.gif
------------------------------------------------------------------------------
    svn:mime-type = image/gif

Added: www-releases/trunk/3.9.1/docs/_static/llvm-theme.css
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_static/llvm-theme.css?rev=290368&view=auto
==============================================================================
--- www-releases/trunk/3.9.1/docs/_static/llvm-theme.css (added)
+++ www-releases/trunk/3.9.1/docs/_static/llvm-theme.css Thu Dec 22 14:04:03 2016
@@ -0,0 +1,371 @@
+/*
+ * sphinxdoc.css_t
+ * ~~~~~~~~~~~~~~~
+ *
+ * Sphinx stylesheet -- sphinxdoc theme.  Originally created by
+ * Armin Ronacher for Werkzeug.
+ *
+ * :copyright: Copyright 2007-2010 by the Sphinx team, see AUTHORS.
+ * :license: BSD, see LICENSE for details.
+ *
+ */
+
+ at import url("basic.css");
+
+/* -- page layout ----------------------------------------------------------- */
+
+body {
+    font-family: 'Lucida Grande', 'Lucida Sans Unicode', 'Geneva',
+                 'Verdana', sans-serif;
+    font-size: 14px;
+    line-height: 150%;
+    text-align: center;
+    background-color: #BFD1D4;
+    color: black;
+    padding: 0;
+    border: 1px solid #aaa;
+
+    margin: 0px 80px 0px 80px;
+    min-width: 740px;
+}
+
+div.logo {
+    background-color: white;
+    text-align: left;
+    padding: 10px 10px 15px 15px;
+}
+
+div.document {
+    background-color: white;
+    text-align: left;
+    background-image: url(contents.png);
+    background-repeat: repeat-x;
+}
+
+div.bodywrapper {
+    margin: 0 240px 0 0;
+    border-right: 1px solid #ccc;
+}
+
+div.body {
+    margin: 0;
+    padding: 0.5em 20px 20px 20px;
+}
+
+div.related {
+    font-size: 1em;
+}
+
+div.related ul {
+    background-image: url(navigation.png);
+    height: 2em;
+    border-top: 1px solid #ddd;
+    border-bottom: 1px solid #ddd;
+}
+
+div.related ul li {
+    margin: 0;
+    padding: 0;
+    height: 2em;
+    float: left;
+}
+
+div.related ul li.right {
+    float: right;
+    margin-right: 5px;
+}
+
+div.related ul li a {
+    margin: 0;
+    padding: 0 5px 0 5px;
+    line-height: 1.75em;
+    color: #EE9816;
+}
+
+div.related ul li a:hover {
+    color: #3CA8E7;
+}
+
+div.sphinxsidebarwrapper {
+    padding: 0;
+}
+
+div.sphinxsidebar {
+    margin: 0;
+    padding: 0.5em 15px 15px 0;
+    width: 210px;
+    float: right;
+    font-size: 1em;
+    text-align: left;
+}
+
+div.sphinxsidebar h3, div.sphinxsidebar h4 {
+    margin: 1em 0 0.5em 0;
+    font-size: 1em;
+    padding: 0.1em 0 0.1em 0.5em;
+    color: white;
+    border: 1px solid #86989B;
+    background-color: #AFC1C4;
+}
+
+div.sphinxsidebar h3 a {
+    color: white;
+}
+
+div.sphinxsidebar ul {
+    padding-left: 1.5em;
+    margin-top: 7px;
+    padding: 0;
+    line-height: 130%;
+}
+
+div.sphinxsidebar ul ul {
+    margin-left: 20px;
+}
+
+div.footer {
+    background-color: #E3EFF1;
+    color: #86989B;
+    padding: 3px 8px 3px 0;
+    clear: both;
+    font-size: 0.8em;
+    text-align: right;
+}
+
+div.footer a {
+    color: #86989B;
+    text-decoration: underline;
+}
+
+/* -- body styles ----------------------------------------------------------- */
+
+p {
+    margin: 0.8em 0 0.5em 0;
+}
+
+a {
+    color: #CA7900;
+    text-decoration: none;
+}
+
+a:hover {
+    color: #2491CF;
+}
+
+div.body p a{
+    text-decoration: underline;
+}
+
+h1 {
+    margin: 0;
+    padding: 0.7em 0 0.3em 0;
+    font-size: 1.5em;
+    color: #11557C;
+}
+
+h2 {
+    margin: 1.3em 0 0.2em 0;
+    font-size: 1.35em;
+    padding: 0;
+}
+
+h3 {
+    margin: 1em 0 -0.3em 0;
+    font-size: 1.2em;
+}
+
+h3 a:hover {
+    text-decoration: underline;
+}
+
+div.body h1 a, div.body h2 a, div.body h3 a, div.body h4 a, div.body h5 a, div.body h6 a {
+    color: black!important;
+}
+
+div.body h1,
+div.body h2,
+div.body h3,
+div.body h4,
+div.body h5,
+div.body h6 {
+    background-color: #f2f2f2;
+    font-weight: normal;
+    color: #20435c;
+    border-bottom: 1px solid #ccc;
+    margin: 20px -20px 10px -20px;
+    padding: 3px 0 3px 10px;
+}
+
+div.body h1 { margin-top: 0; font-size: 200%; }
+div.body h2 { font-size: 160%; }
+div.body h3 { font-size: 140%; }
+div.body h4 { font-size: 120%; }
+div.body h5 { font-size: 110%; }
+div.body h6 { font-size: 100%; }
+
+h1 a.anchor, h2 a.anchor, h3 a.anchor, h4 a.anchor, h5 a.anchor, h6 a.anchor {
+    display: none;
+    margin: 0 0 0 0.3em;
+    padding: 0 0.2em 0 0.2em;
+    color: #aaa!important;
+}
+
+h1:hover a.anchor, h2:hover a.anchor, h3:hover a.anchor, h4:hover a.anchor,
+h5:hover a.anchor, h6:hover a.anchor {
+    display: inline;
+}
+
+h1 a.anchor:hover, h2 a.anchor:hover, h3 a.anchor:hover, h4 a.anchor:hover,
+h5 a.anchor:hover, h6 a.anchor:hover {
+    color: #777;
+    background-color: #eee;
+}
+
+a.headerlink {
+    color: #c60f0f!important;
+    font-size: 1em;
+    margin-left: 6px;
+    padding: 0 4px 0 4px;
+    text-decoration: none!important;
+}
+
+a.headerlink:hover {
+    background-color: #ccc;
+    color: white!important;
+}
+
+cite, code, tt {
+    font-family: 'Consolas', 'Deja Vu Sans Mono',
+                 'Bitstream Vera Sans Mono', monospace;
+    font-size: 0.95em;
+}
+
+:not(a.reference) > tt {
+    background-color: #f2f2f2;
+    border-bottom: 1px solid #ddd;
+    color: #333;
+}
+
+tt.descname, tt.descclassname, tt.xref {
+    border: 0;
+}
+
+hr {
+    border: 1px solid #abc;
+    margin: 2em;
+}
+
+p a tt {
+    border: 0;
+    color: #CA7900;
+}
+
+p a tt:hover {
+    color: #2491CF;
+}
+
+a tt {
+    border: none;
+}
+
+pre {
+    font-family: 'Consolas', 'Deja Vu Sans Mono',
+                 'Bitstream Vera Sans Mono', monospace;
+    font-size: 0.95em;
+    line-height: 120%;
+    padding: 0.5em;
+    border: 1px solid #ccc;
+    background-color: #f8f8f8;
+}
+
+pre a {
+    color: inherit;
+    text-decoration: underline;
+}
+
+td.linenos pre {
+    padding: 0.5em 0;
+}
+
+div.quotebar {
+    background-color: #f8f8f8;
+    max-width: 250px;
+    float: right;
+    padding: 2px 7px;
+    border: 1px solid #ccc;
+}
+
+div.topic {
+    background-color: #f8f8f8;
+}
+
+table {
+    border-collapse: collapse;
+    margin: 0 -0.5em 0 -0.5em;
+}
+
+table td, table th {
+    padding: 0.2em 0.5em 0.2em 0.5em;
+}
+
+div.admonition, div.warning {
+    font-size: 0.9em;
+    margin: 1em 0 1em 0;
+    border: 1px solid #86989B;
+    background-color: #f7f7f7;
+    padding: 0;
+}
+
+div.admonition p, div.warning p {
+    margin: 0.5em 1em 0.5em 1em;
+    padding: 0;
+}
+
+div.admonition pre, div.warning pre {
+    margin: 0.4em 1em 0.4em 1em;
+}
+
+div.admonition p.admonition-title,
+div.warning p.admonition-title {
+    margin: 0;
+    padding: 0.1em 0 0.1em 0.5em;
+    color: white;
+    border-bottom: 1px solid #86989B;
+    font-weight: bold;
+    background-color: #AFC1C4;
+}
+
+div.warning {
+    border: 1px solid #940000;
+}
+
+div.warning p.admonition-title {
+    background-color: #CF0000;
+    border-bottom-color: #940000;
+}
+
+div.admonition ul, div.admonition ol,
+div.warning ul, div.warning ol {
+    margin: 0.1em 0.5em 0.5em 3em;
+    padding: 0;
+}
+
+div.versioninfo {
+    margin: 1em 0 0 0;
+    border: 1px solid #ccc;
+    background-color: #DDEAF0;
+    padding: 8px;
+    line-height: 1.3em;
+    font-size: 0.9em;
+}
+
+.viewcode-back {
+    font-family: 'Lucida Grande', 'Lucida Sans Unicode', 'Geneva',
+                 'Verdana', sans-serif;
+}
+
+div.viewcode-block:target {
+    background-color: #f4debf;
+    border-top: 1px solid #ac9;
+    border-bottom: 1px solid #ac9;
+}

Added: www-releases/trunk/3.9.1/docs/_static/llvm.css
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_static/llvm.css?rev=290368&view=auto
==============================================================================
--- www-releases/trunk/3.9.1/docs/_static/llvm.css (added)
+++ www-releases/trunk/3.9.1/docs/_static/llvm.css Thu Dec 22 14:04:03 2016
@@ -0,0 +1,112 @@
+/*
+ * LLVM documentation style sheet
+ */
+
+/* Common styles */
+.body { color: black; background: white; margin: 0 0 0 0 }
+
+/* No borders on image links */
+a:link img, a:visited img { border-style: none }
+
+address img { float: right; width: 88px; height: 31px; }
+address     { clear: right; }
+
+table       { text-align: center; border: 2px solid black;
+              border-collapse: collapse; margin-top: 1em; margin-left: 1em;
+              margin-right: 1em; margin-bottom: 1em; }
+tr, td      { border: 2px solid gray; padding: 4pt 4pt 2pt 2pt; }
+th          { border: 2px solid gray; font-weight: bold; font-size: 105%;
+              background: url("lines.gif");
+              font-family: "Georgia,Palatino,Times,Roman,SanSerif";
+              text-align: center; vertical-align: middle; }
+/*
+ * Documentation
+ */
+/* Common for title and header */
+.doc_title, .doc_section, .doc_subsection, h1, h2, h3 {
+  color: black; background: url("lines.gif");
+  font-family: "Georgia,Palatino,Times,Roman,SanSerif"; font-weight: bold;
+  border-width: 1px;
+  border-style: solid none solid none;
+  text-align: center;
+  vertical-align: middle;
+  padding-left: 8pt;
+  padding-top: 1px;
+  padding-bottom: 2px
+}
+
+h1, .doc_title, .title { text-align: left;   font-size: 25pt }
+
+h2, .doc_section   { text-align: center; font-size: 22pt;
+                     margin: 20pt 0pt 5pt 0pt; }
+
+h3, .doc_subsection { width: 75%;
+                      text-align: left;  font-size: 12pt;
+                      padding: 4pt 4pt 4pt 4pt;
+                      margin: 1.5em 0.5em 0.5em 0.5em }
+
+h4, .doc_subsubsection { margin: 2.0em 0.5em 0.5em 0.5em;
+                         font-weight: bold; font-style: oblique;
+                         border-bottom: 1px solid #999999; font-size: 12pt;
+                         width: 75%; }
+
+.doc_author     { text-align: left; font-weight: bold; padding-left: 20pt }
+.doc_text       { text-align: left; padding-left: 20pt; padding-right: 10pt }
+
+.doc_footer     { text-align: left; padding: 0 0 0 0 }
+
+.doc_hilite     { color: blue; font-weight: bold; }
+
+.doc_table      { text-align: center; width: 90%;
+                  padding: 1px 1px 1px 1px; border: 1px; }
+
+.doc_warning    { color: red; font-weight: bold }
+
+/* <div class="doc_code"> would use this class, and <div> adds more padding */
+.doc_code, .literal-block
+                { border: solid 1px gray; background: #eeeeee;
+                  margin: 0 1em 0 1em;
+                  padding: 0 1em 0 1em;
+                  display: table;
+                }
+
+blockquote pre {
+        padding: 1em 2em 1em 1em;
+        border: solid 1px gray;
+        background: #eeeeee;
+        margin: 0 1em 0 1em;
+        display: table;
+}
+
+h2+div, h2+p {text-align: left; padding-left: 20pt; padding-right: 10pt;}
+h3+div, h3+p {text-align: left; padding-left: 20pt; padding-right: 10pt;}
+h4+div, h4+p {text-align: left; padding-left: 20pt; padding-right: 10pt;}
+
+/* It is preferrable to use <pre class="doc_code"> everywhere instead of the
+ * <div class="doc_code"><pre>...</ptr></div> construct.
+ *
+ * Once all docs use <pre> for code regions, this style can  be merged with the
+ * one above, and we can drop the [pre] qualifier.
+ */
+pre.doc_code, .literal-block { padding: 1em 2em 1em 1em }
+
+.doc_notes      { background: #fafafa; border: 1px solid #cecece;
+                  display: table; padding: 0 1em 0 .1em }
+
+table.layout    { text-align: left; border: none; border-collapse: collapse;
+                  padding: 4px 4px 4px 4px; }
+tr.layout, td.layout, td.left, td.right
+                { border: none; padding: 4pt 4pt 2pt 2pt; vertical-align: top; }
+td.left         { text-align: left }
+td.right        { text-align: right }
+th.layout       { border: none; font-weight: bold; font-size: 105%;
+                  text-align: center; vertical-align: middle; }
+
+/* Left align table cell */
+.td_left        { border: 2px solid gray; text-align: left; }
+
+/* ReST-specific */
+.title { margin-top: 0 }
+.topic-title{ display: none }
+div.contents ul { list-style-type: decimal }
+.toc-backref    { color: black; text-decoration: none; }

Added: www-releases/trunk/3.9.1/docs/_static/logo.png
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_static/logo.png?rev=290368&view=auto
==============================================================================
Binary file - no diff available.

Propchange: www-releases/trunk/3.9.1/docs/_static/logo.png
------------------------------------------------------------------------------
    svn:mime-type = image/png

Added: www-releases/trunk/3.9.1/docs/_static/minus.png
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_static/minus.png?rev=290368&view=auto
==============================================================================
Binary file - no diff available.

Propchange: www-releases/trunk/3.9.1/docs/_static/minus.png
------------------------------------------------------------------------------
    svn:mime-type = image/png

Added: www-releases/trunk/3.9.1/docs/_static/navigation.png
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_static/navigation.png?rev=290368&view=auto
==============================================================================
Binary file - no diff available.

Propchange: www-releases/trunk/3.9.1/docs/_static/navigation.png
------------------------------------------------------------------------------
    svn:mime-type = image/png

Added: www-releases/trunk/3.9.1/docs/_static/plus.png
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_static/plus.png?rev=290368&view=auto
==============================================================================
Binary file - no diff available.

Propchange: www-releases/trunk/3.9.1/docs/_static/plus.png
------------------------------------------------------------------------------
    svn:mime-type = image/png

Added: www-releases/trunk/3.9.1/docs/_static/pygments.css
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_static/pygments.css?rev=290368&view=auto
==============================================================================
--- www-releases/trunk/3.9.1/docs/_static/pygments.css (added)
+++ www-releases/trunk/3.9.1/docs/_static/pygments.css Thu Dec 22 14:04:03 2016
@@ -0,0 +1,62 @@
+.highlight .hll { background-color: #ffffcc }
+.highlight  { background: #f0f0f0; }
+.highlight .c { color: #60a0b0; font-style: italic } /* Comment */
+.highlight .err { border: 1px solid #FF0000 } /* Error */
+.highlight .k { color: #007020; font-weight: bold } /* Keyword */
+.highlight .o { color: #666666 } /* Operator */
+.highlight .cm { color: #60a0b0; font-style: italic } /* Comment.Multiline */
+.highlight .cp { color: #007020 } /* Comment.Preproc */
+.highlight .c1 { color: #60a0b0; font-style: italic } /* Comment.Single */
+.highlight .cs { color: #60a0b0; background-color: #fff0f0 } /* Comment.Special */
+.highlight .gd { color: #A00000 } /* Generic.Deleted */
+.highlight .ge { font-style: italic } /* Generic.Emph */
+.highlight .gr { color: #FF0000 } /* Generic.Error */
+.highlight .gh { color: #000080; font-weight: bold } /* Generic.Heading */
+.highlight .gi { color: #00A000 } /* Generic.Inserted */
+.highlight .go { color: #888888 } /* Generic.Output */
+.highlight .gp { color: #c65d09; font-weight: bold } /* Generic.Prompt */
+.highlight .gs { font-weight: bold } /* Generic.Strong */
+.highlight .gu { color: #800080; font-weight: bold } /* Generic.Subheading */
+.highlight .gt { color: #0044DD } /* Generic.Traceback */
+.highlight .kc { color: #007020; font-weight: bold } /* Keyword.Constant */
+.highlight .kd { color: #007020; font-weight: bold } /* Keyword.Declaration */
+.highlight .kn { color: #007020; font-weight: bold } /* Keyword.Namespace */
+.highlight .kp { color: #007020 } /* Keyword.Pseudo */
+.highlight .kr { color: #007020; font-weight: bold } /* Keyword.Reserved */
+.highlight .kt { color: #902000 } /* Keyword.Type */
+.highlight .m { color: #40a070 } /* Literal.Number */
+.highlight .s { color: #4070a0 } /* Literal.String */
+.highlight .na { color: #4070a0 } /* Name.Attribute */
+.highlight .nb { color: #007020 } /* Name.Builtin */
+.highlight .nc { color: #0e84b5; font-weight: bold } /* Name.Class */
+.highlight .no { color: #60add5 } /* Name.Constant */
+.highlight .nd { color: #555555; font-weight: bold } /* Name.Decorator */
+.highlight .ni { color: #d55537; font-weight: bold } /* Name.Entity */
+.highlight .ne { color: #007020 } /* Name.Exception */
+.highlight .nf { color: #06287e } /* Name.Function */
+.highlight .nl { color: #002070; font-weight: bold } /* Name.Label */
+.highlight .nn { color: #0e84b5; font-weight: bold } /* Name.Namespace */
+.highlight .nt { color: #062873; font-weight: bold } /* Name.Tag */
+.highlight .nv { color: #bb60d5 } /* Name.Variable */
+.highlight .ow { color: #007020; font-weight: bold } /* Operator.Word */
+.highlight .w { color: #bbbbbb } /* Text.Whitespace */
+.highlight .mf { color: #40a070 } /* Literal.Number.Float */
+.highlight .mh { color: #40a070 } /* Literal.Number.Hex */
+.highlight .mi { color: #40a070 } /* Literal.Number.Integer */
+.highlight .mo { color: #40a070 } /* Literal.Number.Oct */
+.highlight .sb { color: #4070a0 } /* Literal.String.Backtick */
+.highlight .sc { color: #4070a0 } /* Literal.String.Char */
+.highlight .sd { color: #4070a0; font-style: italic } /* Literal.String.Doc */
+.highlight .s2 { color: #4070a0 } /* Literal.String.Double */
+.highlight .se { color: #4070a0; font-weight: bold } /* Literal.String.Escape */
+.highlight .sh { color: #4070a0 } /* Literal.String.Heredoc */
+.highlight .si { color: #70a0d0; font-style: italic } /* Literal.String.Interpol */
+.highlight .sx { color: #c65d09 } /* Literal.String.Other */
+.highlight .sr { color: #235388 } /* Literal.String.Regex */
+.highlight .s1 { color: #4070a0 } /* Literal.String.Single */
+.highlight .ss { color: #517918 } /* Literal.String.Symbol */
+.highlight .bp { color: #007020 } /* Name.Builtin.Pseudo */
+.highlight .vc { color: #bb60d5 } /* Name.Variable.Class */
+.highlight .vg { color: #bb60d5 } /* Name.Variable.Global */
+.highlight .vi { color: #bb60d5 } /* Name.Variable.Instance */
+.highlight .il { color: #40a070 } /* Literal.Number.Integer.Long */
\ No newline at end of file

Added: www-releases/trunk/3.9.1/docs/_static/searchtools.js
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_static/searchtools.js?rev=290368&view=auto
==============================================================================
--- www-releases/trunk/3.9.1/docs/_static/searchtools.js (added)
+++ www-releases/trunk/3.9.1/docs/_static/searchtools.js Thu Dec 22 14:04:03 2016
@@ -0,0 +1,622 @@
+/*
+ * searchtools.js_t
+ * ~~~~~~~~~~~~~~~~
+ *
+ * Sphinx JavaScript utilties for the full-text search.
+ *
+ * :copyright: Copyright 2007-2014 by the Sphinx team, see AUTHORS.
+ * :license: BSD, see LICENSE for details.
+ *
+ */
+
+
+/**
+ * Porter Stemmer
+ */
+var Stemmer = function() {
+
+  var step2list = {
+    ational: 'ate',
+    tional: 'tion',
+    enci: 'ence',
+    anci: 'ance',
+    izer: 'ize',
+    bli: 'ble',
+    alli: 'al',
+    entli: 'ent',
+    eli: 'e',
+    ousli: 'ous',
+    ization: 'ize',
+    ation: 'ate',
+    ator: 'ate',
+    alism: 'al',
+    iveness: 'ive',
+    fulness: 'ful',
+    ousness: 'ous',
+    aliti: 'al',
+    iviti: 'ive',
+    biliti: 'ble',
+    logi: 'log'
+  };
+
+  var step3list = {
+    icate: 'ic',
+    ative: '',
+    alize: 'al',
+    iciti: 'ic',
+    ical: 'ic',
+    ful: '',
+    ness: ''
+  };
+
+  var c = "[^aeiou]";          // consonant
+  var v = "[aeiouy]";          // vowel
+  var C = c + "[^aeiouy]*";    // consonant sequence
+  var V = v + "[aeiou]*";      // vowel sequence
+
+  var mgr0 = "^(" + C + ")?" + V + C;                      // [C]VC... is m>0
+  var meq1 = "^(" + C + ")?" + V + C + "(" + V + ")?$";    // [C]VC[V] is m=1
+  var mgr1 = "^(" + C + ")?" + V + C + V + C;              // [C]VCVC... is m>1
+  var s_v   = "^(" + C + ")?" + v;                         // vowel in stem
+
+  this.stemWord = function (w) {
+    var stem;
+    var suffix;
+    var firstch;
+    var origword = w;
+
+    if (w.length < 3)
+      return w;
+
+    var re;
+    var re2;
+    var re3;
+    var re4;
+
+    firstch = w.substr(0,1);
+    if (firstch == "y")
+      w = firstch.toUpperCase() + w.substr(1);
+
+    // Step 1a
+    re = /^(.+?)(ss|i)es$/;
+    re2 = /^(.+?)([^s])s$/;
+
+    if (re.test(w))
+      w = w.replace(re,"$1$2");
+    else if (re2.test(w))
+      w = w.replace(re2,"$1$2");
+
+    // Step 1b
+    re = /^(.+?)eed$/;
+    re2 = /^(.+?)(ed|ing)$/;
+    if (re.test(w)) {
+      var fp = re.exec(w);
+      re = new RegExp(mgr0);
+      if (re.test(fp[1])) {
+        re = /.$/;
+        w = w.replace(re,"");
+      }
+    }
+    else if (re2.test(w)) {
+      var fp = re2.exec(w);
+      stem = fp[1];
+      re2 = new RegExp(s_v);
+      if (re2.test(stem)) {
+        w = stem;
+        re2 = /(at|bl|iz)$/;
+        re3 = new RegExp("([^aeiouylsz])\\1$");
+        re4 = new RegExp("^" + C + v + "[^aeiouwxy]$");
+        if (re2.test(w))
+          w = w + "e";
+        else if (re3.test(w)) {
+          re = /.$/;
+          w = w.replace(re,"");
+        }
+        else if (re4.test(w))
+          w = w + "e";
+      }
+    }
+
+    // Step 1c
+    re = /^(.+?)y$/;
+    if (re.test(w)) {
+      var fp = re.exec(w);
+      stem = fp[1];
+      re = new RegExp(s_v);
+      if (re.test(stem))
+        w = stem + "i";
+    }
+
+    // Step 2
+    re = /^(.+?)(ational|tional|enci|anci|izer|bli|alli|entli|eli|ousli|ization|ation|ator|alism|iveness|fulness|ousness|aliti|iviti|biliti|logi)$/;
+    if (re.test(w)) {
+      var fp = re.exec(w);
+      stem = fp[1];
+      suffix = fp[2];
+      re = new RegExp(mgr0);
+      if (re.test(stem))
+        w = stem + step2list[suffix];
+    }
+
+    // Step 3
+    re = /^(.+?)(icate|ative|alize|iciti|ical|ful|ness)$/;
+    if (re.test(w)) {
+      var fp = re.exec(w);
+      stem = fp[1];
+      suffix = fp[2];
+      re = new RegExp(mgr0);
+      if (re.test(stem))
+        w = stem + step3list[suffix];
+    }
+
+    // Step 4
+    re = /^(.+?)(al|ance|ence|er|ic|able|ible|ant|ement|ment|ent|ou|ism|ate|iti|ous|ive|ize)$/;
+    re2 = /^(.+?)(s|t)(ion)$/;
+    if (re.test(w)) {
+      var fp = re.exec(w);
+      stem = fp[1];
+      re = new RegExp(mgr1);
+      if (re.test(stem))
+        w = stem;
+    }
+    else if (re2.test(w)) {
+      var fp = re2.exec(w);
+      stem = fp[1] + fp[2];
+      re2 = new RegExp(mgr1);
+      if (re2.test(stem))
+        w = stem;
+    }
+
+    // Step 5
+    re = /^(.+?)e$/;
+    if (re.test(w)) {
+      var fp = re.exec(w);
+      stem = fp[1];
+      re = new RegExp(mgr1);
+      re2 = new RegExp(meq1);
+      re3 = new RegExp("^" + C + v + "[^aeiouwxy]$");
+      if (re.test(stem) || (re2.test(stem) && !(re3.test(stem))))
+        w = stem;
+    }
+    re = /ll$/;
+    re2 = new RegExp(mgr1);
+    if (re.test(w) && re2.test(w)) {
+      re = /.$/;
+      w = w.replace(re,"");
+    }
+
+    // and turn initial Y back to y
+    if (firstch == "y")
+      w = firstch.toLowerCase() + w.substr(1);
+    return w;
+  }
+}
+
+
+
+/**
+ * Simple result scoring code.
+ */
+var Scorer = {
+  // Implement the following function to further tweak the score for each result
+  // The function takes a result array [filename, title, anchor, descr, score]
+  // and returns the new score.
+  /*
+  score: function(result) {
+    return result[4];
+  },
+  */
+
+  // query matches the full name of an object
+  objNameMatch: 11,
+  // or matches in the last dotted part of the object name
+  objPartialMatch: 6,
+  // Additive scores depending on the priority of the object
+  objPrio: {0:  15,   // used to be importantResults
+            1:  5,   // used to be objectResults
+            2: -5},  // used to be unimportantResults
+  //  Used when the priority is not in the mapping.
+  objPrioDefault: 0,
+
+  // query found in title
+  title: 15,
+  // query found in terms
+  term: 5
+};
+
+
+/**
+ * Search Module
+ */
+var Search = {
+
+  _index : null,
+  _queued_query : null,
+  _pulse_status : -1,
+
+  init : function() {
+      var params = $.getQueryParameters();
+      if (params.q) {
+          var query = params.q[0];
+          $('input[name="q"]')[0].value = query;
+          this.performSearch(query);
+      }
+  },
+
+  loadIndex : function(url) {
+    $.ajax({type: "GET", url: url, data: null,
+            dataType: "script", cache: true,
+            complete: function(jqxhr, textstatus) {
+              if (textstatus != "success") {
+                document.getElementById("searchindexloader").src = url;
+              }
+            }});
+  },
+
+  setIndex : function(index) {
+    var q;
+    this._index = index;
+    if ((q = this._queued_query) !== null) {
+      this._queued_query = null;
+      Search.query(q);
+    }
+  },
+
+  hasIndex : function() {
+      return this._index !== null;
+  },
+
+  deferQuery : function(query) {
+      this._queued_query = query;
+  },
+
+  stopPulse : function() {
+      this._pulse_status = 0;
+  },
+
+  startPulse : function() {
+    if (this._pulse_status >= 0)
+        return;
+    function pulse() {
+      var i;
+      Search._pulse_status = (Search._pulse_status + 1) % 4;
+      var dotString = '';
+      for (i = 0; i < Search._pulse_status; i++)
+        dotString += '.';
+      Search.dots.text(dotString);
+      if (Search._pulse_status > -1)
+        window.setTimeout(pulse, 500);
+    }
+    pulse();
+  },
+
+  /**
+   * perform a search for something (or wait until index is loaded)
+   */
+  performSearch : function(query) {
+    // create the required interface elements
+    this.out = $('#search-results');
+    this.title = $('<h2>' + _('Searching') + '</h2>').appendTo(this.out);
+    this.dots = $('<span></span>').appendTo(this.title);
+    this.status = $('<p style="display: none"></p>').appendTo(this.out);
+    this.output = $('<ul class="search"/>').appendTo(this.out);
+
+    $('#search-progress').text(_('Preparing search...'));
+    this.startPulse();
+
+    // index already loaded, the browser was quick!
+    if (this.hasIndex())
+      this.query(query);
+    else
+      this.deferQuery(query);
+  },
+
+  /**
+   * execute search (requires search index to be loaded)
+   */
+  query : function(query) {
+    var i;
+    var stopwords = ["a","and","are","as","at","be","but","by","for","if","in","into","is","it","near","no","not","of","on","or","such","that","the","their","then","there","these","they","this","to","was","will","with"];
+
+    // stem the searchterms and add them to the correct list
+    var stemmer = new Stemmer();
+    var searchterms = [];
+    var excluded = [];
+    var hlterms = [];
+    var tmp = query.split(/\s+/);
+    var objectterms = [];
+    for (i = 0; i < tmp.length; i++) {
+      if (tmp[i] !== "") {
+          objectterms.push(tmp[i].toLowerCase());
+      }
+
+      if ($u.indexOf(stopwords, tmp[i].toLowerCase()) != -1 || tmp[i].match(/^\d+$/) ||
+          tmp[i] === "") {
+        // skip this "word"
+        continue;
+      }
+      // stem the word
+      var word = stemmer.stemWord(tmp[i].toLowerCase());
+      var toAppend;
+      // select the correct list
+      if (word[0] == '-') {
+        toAppend = excluded;
+        word = word.substr(1);
+      }
+      else {
+        toAppend = searchterms;
+        hlterms.push(tmp[i].toLowerCase());
+      }
+      // only add if not already in the list
+      if (!$u.contains(toAppend, word))
+        toAppend.push(word);
+    }
+    var highlightstring = '?highlight=' + $.urlencode(hlterms.join(" "));
+
+    // console.debug('SEARCH: searching for:');
+    // console.info('required: ', searchterms);
+    // console.info('excluded: ', excluded);
+
+    // prepare search
+    var terms = this._index.terms;
+    var titleterms = this._index.titleterms;
+
+    // array of [filename, title, anchor, descr, score]
+    var results = [];
+    $('#search-progress').empty();
+
+    // lookup as object
+    for (i = 0; i < objectterms.length; i++) {
+      var others = [].concat(objectterms.slice(0, i),
+                             objectterms.slice(i+1, objectterms.length));
+      results = results.concat(this.performObjectSearch(objectterms[i], others));
+    }
+
+    // lookup as search terms in fulltext
+    results = results.concat(this.performTermsSearch(searchterms, excluded, terms, Scorer.term))
+                     .concat(this.performTermsSearch(searchterms, excluded, titleterms, Scorer.title));
+
+    // let the scorer override scores with a custom scoring function
+    if (Scorer.score) {
+      for (i = 0; i < results.length; i++)
+        results[i][4] = Scorer.score(results[i]);
+    }
+
+    // now sort the results by score (in opposite order of appearance, since the
+    // display function below uses pop() to retrieve items) and then
+    // alphabetically
+    results.sort(function(a, b) {
+      var left = a[4];
+      var right = b[4];
+      if (left > right) {
+        return 1;
+      } else if (left < right) {
+        return -1;
+      } else {
+        // same score: sort alphabetically
+        left = a[1].toLowerCase();
+        right = b[1].toLowerCase();
+        return (left > right) ? -1 : ((left < right) ? 1 : 0);
+      }
+    });
+
+    // for debugging
+    //Search.lastresults = results.slice();  // a copy
+    //console.info('search results:', Search.lastresults);
+
+    // print the results
+    var resultCount = results.length;
+    function displayNextItem() {
+      // results left, load the summary and display it
+      if (results.length) {
+        var item = results.pop();
+        var listItem = $('<li style="display:none"></li>');
+        if (DOCUMENTATION_OPTIONS.FILE_SUFFIX === '') {
+          // dirhtml builder
+          var dirname = item[0] + '/';
+          if (dirname.match(/\/index\/$/)) {
+            dirname = dirname.substring(0, dirname.length-6);
+          } else if (dirname == 'index/') {
+            dirname = '';
+          }
+          listItem.append($('<a/>').attr('href',
+            DOCUMENTATION_OPTIONS.URL_ROOT + dirname +
+            highlightstring + item[2]).html(item[1]));
+        } else {
+          // normal html builders
+          listItem.append($('<a/>').attr('href',
+            item[0] + DOCUMENTATION_OPTIONS.FILE_SUFFIX +
+            highlightstring + item[2]).html(item[1]));
+        }
+        if (item[3]) {
+          listItem.append($('<span> (' + item[3] + ')</span>'));
+          Search.output.append(listItem);
+          listItem.slideDown(5, function() {
+            displayNextItem();
+          });
+        } else if (DOCUMENTATION_OPTIONS.HAS_SOURCE) {
+          $.ajax({url: DOCUMENTATION_OPTIONS.URL_ROOT + '_sources/' + item[0] + '.txt',
+                  dataType: "text",
+                  complete: function(jqxhr, textstatus) {
+                    var data = jqxhr.responseText;
+                    if (data !== '') {
+                      listItem.append(Search.makeSearchSummary(data, searchterms, hlterms));
+                    }
+                    Search.output.append(listItem);
+                    listItem.slideDown(5, function() {
+                      displayNextItem();
+                    });
+                  }});
+        } else {
+          // no source available, just display title
+          Search.output.append(listItem);
+          listItem.slideDown(5, function() {
+            displayNextItem();
+          });
+        }
+      }
+      // search finished, update title and status message
+      else {
+        Search.stopPulse();
+        Search.title.text(_('Search Results'));
+        if (!resultCount)
+          Search.status.text(_('Your search did not match any documents. Please make sure that all words are spelled correctly and that you\'ve selected enough categories.'));
+        else
+            Search.status.text(_('Search finished, found %s page(s) matching the search query.').replace('%s', resultCount));
+        Search.status.fadeIn(500);
+      }
+    }
+    displayNextItem();
+  },
+
+  /**
+   * search for object names
+   */
+  performObjectSearch : function(object, otherterms) {
+    var filenames = this._index.filenames;
+    var objects = this._index.objects;
+    var objnames = this._index.objnames;
+    var titles = this._index.titles;
+
+    var i;
+    var results = [];
+
+    for (var prefix in objects) {
+      for (var name in objects[prefix]) {
+        var fullname = (prefix ? prefix + '.' : '') + name;
+        if (fullname.toLowerCase().indexOf(object) > -1) {
+          var score = 0;
+          var parts = fullname.split('.');
+          // check for different match types: exact matches of full name or
+          // "last name" (i.e. last dotted part)
+          if (fullname == object || parts[parts.length - 1] == object) {
+            score += Scorer.objNameMatch;
+          // matches in last name
+          } else if (parts[parts.length - 1].indexOf(object) > -1) {
+            score += Scorer.objPartialMatch;
+          }
+          var match = objects[prefix][name];
+          var objname = objnames[match[1]][2];
+          var title = titles[match[0]];
+          // If more than one term searched for, we require other words to be
+          // found in the name/title/description
+          if (otherterms.length > 0) {
+            var haystack = (prefix + ' ' + name + ' ' +
+                            objname + ' ' + title).toLowerCase();
+            var allfound = true;
+            for (i = 0; i < otherterms.length; i++) {
+              if (haystack.indexOf(otherterms[i]) == -1) {
+                allfound = false;
+                break;
+              }
+            }
+            if (!allfound) {
+              continue;
+            }
+          }
+          var descr = objname + _(', in ') + title;
+
+          var anchor = match[3];
+          if (anchor === '')
+            anchor = fullname;
+          else if (anchor == '-')
+            anchor = objnames[match[1]][1] + '-' + fullname;
+          // add custom score for some objects according to scorer
+          if (Scorer.objPrio.hasOwnProperty(match[2])) {
+            score += Scorer.objPrio[match[2]];
+          } else {
+            score += Scorer.objPrioDefault;
+          }
+          results.push([filenames[match[0]], fullname, '#'+anchor, descr, score]);
+        }
+      }
+    }
+
+    return results;
+  },
+
+  /**
+   * search for full-text terms in the index
+   */
+  performTermsSearch : function(searchterms, excluded, terms, score) {
+    var filenames = this._index.filenames;
+    var titles = this._index.titles;
+
+    var i, j, file, files;
+    var fileMap = {};
+    var results = [];
+
+    // perform the search on the required terms
+    for (i = 0; i < searchterms.length; i++) {
+      var word = searchterms[i];
+      // no match but word was a required one
+      if ((files = terms[word]) === undefined)
+        break;
+      if (files.length === undefined) {
+        files = [files];
+      }
+      // create the mapping
+      for (j = 0; j < files.length; j++) {
+        file = files[j];
+        if (file in fileMap)
+          fileMap[file].push(word);
+        else
+          fileMap[file] = [word];
+      }
+    }
+
+    // now check if the files don't contain excluded terms
+    for (file in fileMap) {
+      var valid = true;
+
+      // check if all requirements are matched
+      if (fileMap[file].length != searchterms.length)
+          continue;
+
+      // ensure that none of the excluded terms is in the search result
+      for (i = 0; i < excluded.length; i++) {
+        if (terms[excluded[i]] == file ||
+          $u.contains(terms[excluded[i]] || [], file)) {
+          valid = false;
+          break;
+        }
+      }
+
+      // if we have still a valid result we can add it to the result list
+      if (valid) {
+        results.push([filenames[file], titles[file], '', null, score]);
+      }
+    }
+    return results;
+  },
+
+  /**
+   * helper function to return a node containing the
+   * search summary for a given text. keywords is a list
+   * of stemmed words, hlwords is the list of normal, unstemmed
+   * words. the first one is used to find the occurance, the
+   * latter for highlighting it.
+   */
+  makeSearchSummary : function(text, keywords, hlwords) {
+    var textLower = text.toLowerCase();
+    var start = 0;
+    $.each(keywords, function() {
+      var i = textLower.indexOf(this.toLowerCase());
+      if (i > -1)
+        start = i;
+    });
+    start = Math.max(start - 120, 0);
+    var excerpt = ((start > 0) ? '...' : '') +
+      $.trim(text.substr(start, 240)) +
+      ((start + 240 - text.length) ? '...' : '');
+    var rv = $('<div class="context"></div>').text(excerpt);
+    $.each(hlwords, function() {
+      rv = rv.highlightText(this, 'highlighted');
+    });
+    return rv;
+  }
+};
+
+$(document).ready(function() {
+  Search.init();
+});
\ No newline at end of file

Added: www-releases/trunk/3.9.1/docs/_static/underscore.js
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_static/underscore.js?rev=290368&view=auto
==============================================================================
--- www-releases/trunk/3.9.1/docs/_static/underscore.js (added)
+++ www-releases/trunk/3.9.1/docs/_static/underscore.js Thu Dec 22 14:04:03 2016
@@ -0,0 +1,31 @@
+// Underscore.js 1.3.1
+// (c) 2009-2012 Jeremy Ashkenas, DocumentCloud Inc.
+// Underscore is freely distributable under the MIT license.
+// Portions of Underscore are inspired or borrowed from Prototype,
+// Oliver Steele's Functional, and John Resig's Micro-Templating.
+// For all details and documentation:
+// http://documentcloud.github.com/underscore
+(function(){function q(a,c,d){if(a===c)return a!==0||1/a==1/c;if(a==null||c==null)return a===c;if(a._chain)a=a._wrapped;if(c._chain)c=c._wrapped;if(a.isEqual&&b.isFunction(a.isEqual))return a.isEqual(c);if(c.isEqual&&b.isFunction(c.isEqual))return c.isEqual(a);var e=l.call(a);if(e!=l.call(c))return false;switch(e){case "[object String]":return a==String(c);case "[object Number]":return a!=+a?c!=+c:a==0?1/a==1/c:a==+c;case "[object Date]":case "[object Boolean]":return+a==+c;case "[object RegExp]":return a.source==
+c.source&&a.global==c.global&&a.multiline==c.multiline&&a.ignoreCase==c.ignoreCase}if(typeof a!="object"||typeof c!="object")return false;for(var f=d.length;f--;)if(d[f]==a)return true;d.push(a);var f=0,g=true;if(e=="[object Array]"){if(f=a.length,g=f==c.length)for(;f--;)if(!(g=f in a==f in c&&q(a[f],c[f],d)))break}else{if("constructor"in a!="constructor"in c||a.constructor!=c.constructor)return false;for(var h in a)if(b.has(a,h)&&(f++,!(g=b.has(c,h)&&q(a[h],c[h],d))))break;if(g){for(h in c)if(b.has(c,
+h)&&!f--)break;g=!f}}d.pop();return g}var r=this,G=r._,n={},k=Array.prototype,o=Object.prototype,i=k.slice,H=k.unshift,l=o.toString,I=o.hasOwnProperty,w=k.forEach,x=k.map,y=k.reduce,z=k.reduceRight,A=k.filter,B=k.every,C=k.some,p=k.indexOf,D=k.lastIndexOf,o=Array.isArray,J=Object.keys,s=Function.prototype.bind,b=function(a){return new m(a)};if(typeof exports!=="undefined"){if(typeof module!=="undefined"&&module.exports)exports=module.exports=b;exports._=b}else r._=b;b.VERSION="1.3.1";var j=b.each=
+b.forEach=function(a,c,d){if(a!=null)if(w&&a.forEach===w)a.forEach(c,d);else if(a.length===+a.length)for(var e=0,f=a.length;e<f;e++){if(e in a&&c.call(d,a[e],e,a)===n)break}else for(e in a)if(b.has(a,e)&&c.call(d,a[e],e,a)===n)break};b.map=b.collect=function(a,c,b){var e=[];if(a==null)return e;if(x&&a.map===x)return a.map(c,b);j(a,function(a,g,h){e[e.length]=c.call(b,a,g,h)});if(a.length===+a.length)e.length=a.length;return e};b.reduce=b.foldl=b.inject=function(a,c,d,e){var f=arguments.length>2;a==
+null&&(a=[]);if(y&&a.reduce===y)return e&&(c=b.bind(c,e)),f?a.reduce(c,d):a.reduce(c);j(a,function(a,b,i){f?d=c.call(e,d,a,b,i):(d=a,f=true)});if(!f)throw new TypeError("Reduce of empty array with no initial value");return d};b.reduceRight=b.foldr=function(a,c,d,e){var f=arguments.length>2;a==null&&(a=[]);if(z&&a.reduceRight===z)return e&&(c=b.bind(c,e)),f?a.reduceRight(c,d):a.reduceRight(c);var g=b.toArray(a).reverse();e&&!f&&(c=b.bind(c,e));return f?b.reduce(g,c,d,e):b.reduce(g,c)};b.find=b.detect=
+function(a,c,b){var e;E(a,function(a,g,h){if(c.call(b,a,g,h))return e=a,true});return e};b.filter=b.select=function(a,c,b){var e=[];if(a==null)return e;if(A&&a.filter===A)return a.filter(c,b);j(a,function(a,g,h){c.call(b,a,g,h)&&(e[e.length]=a)});return e};b.reject=function(a,c,b){var e=[];if(a==null)return e;j(a,function(a,g,h){c.call(b,a,g,h)||(e[e.length]=a)});return e};b.every=b.all=function(a,c,b){var e=true;if(a==null)return e;if(B&&a.every===B)return a.every(c,b);j(a,function(a,g,h){if(!(e=
+e&&c.call(b,a,g,h)))return n});return e};var E=b.some=b.any=function(a,c,d){c||(c=b.identity);var e=false;if(a==null)return e;if(C&&a.some===C)return a.some(c,d);j(a,function(a,b,h){if(e||(e=c.call(d,a,b,h)))return n});return!!e};b.include=b.contains=function(a,c){var b=false;if(a==null)return b;return p&&a.indexOf===p?a.indexOf(c)!=-1:b=E(a,function(a){return a===c})};b.invoke=function(a,c){var d=i.call(arguments,2);return b.map(a,function(a){return(b.isFunction(c)?c||a:a[c]).apply(a,d)})};b.pluck=
+function(a,c){return b.map(a,function(a){return a[c]})};b.max=function(a,c,d){if(!c&&b.isArray(a))return Math.max.apply(Math,a);if(!c&&b.isEmpty(a))return-Infinity;var e={computed:-Infinity};j(a,function(a,b,h){b=c?c.call(d,a,b,h):a;b>=e.computed&&(e={value:a,computed:b})});return e.value};b.min=function(a,c,d){if(!c&&b.isArray(a))return Math.min.apply(Math,a);if(!c&&b.isEmpty(a))return Infinity;var e={computed:Infinity};j(a,function(a,b,h){b=c?c.call(d,a,b,h):a;b<e.computed&&(e={value:a,computed:b})});
+return e.value};b.shuffle=function(a){var b=[],d;j(a,function(a,f){f==0?b[0]=a:(d=Math.floor(Math.random()*(f+1)),b[f]=b[d],b[d]=a)});return b};b.sortBy=function(a,c,d){return b.pluck(b.map(a,function(a,b,g){return{value:a,criteria:c.call(d,a,b,g)}}).sort(function(a,b){var c=a.criteria,d=b.criteria;return c<d?-1:c>d?1:0}),"value")};b.groupBy=function(a,c){var d={},e=b.isFunction(c)?c:function(a){return a[c]};j(a,function(a,b){var c=e(a,b);(d[c]||(d[c]=[])).push(a)});return d};b.sortedIndex=function(a,
+c,d){d||(d=b.identity);for(var e=0,f=a.length;e<f;){var g=e+f>>1;d(a[g])<d(c)?e=g+1:f=g}return e};b.toArray=function(a){return!a?[]:a.toArray?a.toArray():b.isArray(a)?i.call(a):b.isArguments(a)?i.call(a):b.values(a)};b.size=function(a){return b.toArray(a).length};b.first=b.head=function(a,b,d){return b!=null&&!d?i.call(a,0,b):a[0]};b.initial=function(a,b,d){return i.call(a,0,a.length-(b==null||d?1:b))};b.last=function(a,b,d){return b!=null&&!d?i.call(a,Math.max(a.length-b,0)):a[a.length-1]};b.rest=
+b.tail=function(a,b,d){return i.call(a,b==null||d?1:b)};b.compact=function(a){return b.filter(a,function(a){return!!a})};b.flatten=function(a,c){return b.reduce(a,function(a,e){if(b.isArray(e))return a.concat(c?e:b.flatten(e));a[a.length]=e;return a},[])};b.without=function(a){return b.difference(a,i.call(arguments,1))};b.uniq=b.unique=function(a,c,d){var d=d?b.map(a,d):a,e=[];b.reduce(d,function(d,g,h){if(0==h||(c===true?b.last(d)!=g:!b.include(d,g)))d[d.length]=g,e[e.length]=a[h];return d},[]);
+return e};b.union=function(){return b.uniq(b.flatten(arguments,true))};b.intersection=b.intersect=function(a){var c=i.call(arguments,1);return b.filter(b.uniq(a),function(a){return b.every(c,function(c){return b.indexOf(c,a)>=0})})};b.difference=function(a){var c=b.flatten(i.call(arguments,1));return b.filter(a,function(a){return!b.include(c,a)})};b.zip=function(){for(var a=i.call(arguments),c=b.max(b.pluck(a,"length")),d=Array(c),e=0;e<c;e++)d[e]=b.pluck(a,""+e);return d};b.indexOf=function(a,c,
+d){if(a==null)return-1;var e;if(d)return d=b.sortedIndex(a,c),a[d]===c?d:-1;if(p&&a.indexOf===p)return a.indexOf(c);for(d=0,e=a.length;d<e;d++)if(d in a&&a[d]===c)return d;return-1};b.lastIndexOf=function(a,b){if(a==null)return-1;if(D&&a.lastIndexOf===D)return a.lastIndexOf(b);for(var d=a.length;d--;)if(d in a&&a[d]===b)return d;return-1};b.range=function(a,b,d){arguments.length<=1&&(b=a||0,a=0);for(var d=arguments[2]||1,e=Math.max(Math.ceil((b-a)/d),0),f=0,g=Array(e);f<e;)g[f++]=a,a+=d;return g};
+var F=function(){};b.bind=function(a,c){var d,e;if(a.bind===s&&s)return s.apply(a,i.call(arguments,1));if(!b.isFunction(a))throw new TypeError;e=i.call(arguments,2);return d=function(){if(!(this instanceof d))return a.apply(c,e.concat(i.call(arguments)));F.prototype=a.prototype;var b=new F,g=a.apply(b,e.concat(i.call(arguments)));return Object(g)===g?g:b}};b.bindAll=function(a){var c=i.call(arguments,1);c.length==0&&(c=b.functions(a));j(c,function(c){a[c]=b.bind(a[c],a)});return a};b.memoize=function(a,
+c){var d={};c||(c=b.identity);return function(){var e=c.apply(this,arguments);return b.has(d,e)?d[e]:d[e]=a.apply(this,arguments)}};b.delay=function(a,b){var d=i.call(arguments,2);return setTimeout(function(){return a.apply(a,d)},b)};b.defer=function(a){return b.delay.apply(b,[a,1].concat(i.call(arguments,1)))};b.throttle=function(a,c){var d,e,f,g,h,i=b.debounce(function(){h=g=false},c);return function(){d=this;e=arguments;var b;f||(f=setTimeout(function(){f=null;h&&a.apply(d,e);i()},c));g?h=true:
+a.apply(d,e);i();g=true}};b.debounce=function(a,b){var d;return function(){var e=this,f=arguments;clearTimeout(d);d=setTimeout(function(){d=null;a.apply(e,f)},b)}};b.once=function(a){var b=false,d;return function(){if(b)return d;b=true;return d=a.apply(this,arguments)}};b.wrap=function(a,b){return function(){var d=[a].concat(i.call(arguments,0));return b.apply(this,d)}};b.compose=function(){var a=arguments;return function(){for(var b=arguments,d=a.length-1;d>=0;d--)b=[a[d].apply(this,b)];return b[0]}};
+b.after=function(a,b){return a<=0?b():function(){if(--a<1)return b.apply(this,arguments)}};b.keys=J||function(a){if(a!==Object(a))throw new TypeError("Invalid object");var c=[],d;for(d in a)b.has(a,d)&&(c[c.length]=d);return c};b.values=function(a){return b.map(a,b.identity)};b.functions=b.methods=function(a){var c=[],d;for(d in a)b.isFunction(a[d])&&c.push(d);return c.sort()};b.extend=function(a){j(i.call(arguments,1),function(b){for(var d in b)a[d]=b[d]});return a};b.defaults=function(a){j(i.call(arguments,
+1),function(b){for(var d in b)a[d]==null&&(a[d]=b[d])});return a};b.clone=function(a){return!b.isObject(a)?a:b.isArray(a)?a.slice():b.extend({},a)};b.tap=function(a,b){b(a);return a};b.isEqual=function(a,b){return q(a,b,[])};b.isEmpty=function(a){if(b.isArray(a)||b.isString(a))return a.length===0;for(var c in a)if(b.has(a,c))return false;return true};b.isElement=function(a){return!!(a&&a.nodeType==1)};b.isArray=o||function(a){return l.call(a)=="[object Array]"};b.isObject=function(a){return a===Object(a)};
+b.isArguments=function(a){return l.call(a)=="[object Arguments]"};if(!b.isArguments(arguments))b.isArguments=function(a){return!(!a||!b.has(a,"callee"))};b.isFunction=function(a){return l.call(a)=="[object Function]"};b.isString=function(a){return l.call(a)=="[object String]"};b.isNumber=function(a){return l.call(a)=="[object Number]"};b.isNaN=function(a){return a!==a};b.isBoolean=function(a){return a===true||a===false||l.call(a)=="[object Boolean]"};b.isDate=function(a){return l.call(a)=="[object Date]"};
+b.isRegExp=function(a){return l.call(a)=="[object RegExp]"};b.isNull=function(a){return a===null};b.isUndefined=function(a){return a===void 0};b.has=function(a,b){return I.call(a,b)};b.noConflict=function(){r._=G;return this};b.identity=function(a){return a};b.times=function(a,b,d){for(var e=0;e<a;e++)b.call(d,e)};b.escape=function(a){return(""+a).replace(/&/g,"&").replace(/</g,"<").replace(/>/g,">").replace(/"/g,""").replace(/'/g,"&#x27;").replace(/\//g,"&#x2F;")};b.mixin=function(a){j(b.functions(a),
+function(c){K(c,b[c]=a[c])})};var L=0;b.uniqueId=function(a){var b=L++;return a?a+b:b};b.templateSettings={evaluate:/<%([\s\S]+?)%>/g,interpolate:/<%=([\s\S]+?)%>/g,escape:/<%-([\s\S]+?)%>/g};var t=/.^/,u=function(a){return a.replace(/\\\\/g,"\\").replace(/\\'/g,"'")};b.template=function(a,c){var d=b.templateSettings,d="var __p=[],print=function(){__p.push.apply(__p,arguments);};with(obj||{}){__p.push('"+a.replace(/\\/g,"\\\\").replace(/'/g,"\\'").replace(d.escape||t,function(a,b){return"',_.escape("+
+u(b)+"),'"}).replace(d.interpolate||t,function(a,b){return"',"+u(b)+",'"}).replace(d.evaluate||t,function(a,b){return"');"+u(b).replace(/[\r\n\t]/g," ")+";__p.push('"}).replace(/\r/g,"\\r").replace(/\n/g,"\\n").replace(/\t/g,"\\t")+"');}return __p.join('');",e=new Function("obj","_",d);return c?e(c,b):function(a){return e.call(this,a,b)}};b.chain=function(a){return b(a).chain()};var m=function(a){this._wrapped=a};b.prototype=m.prototype;var v=function(a,c){return c?b(a).chain():a},K=function(a,c){m.prototype[a]=
+function(){var a=i.call(arguments);H.call(a,this._wrapped);return v(c.apply(b,a),this._chain)}};b.mixin(b);j("pop,push,reverse,shift,sort,splice,unshift".split(","),function(a){var b=k[a];m.prototype[a]=function(){var d=this._wrapped;b.apply(d,arguments);var e=d.length;(a=="shift"||a=="splice")&&e===0&&delete d[0];return v(d,this._chain)}});j(["concat","join","slice"],function(a){var b=k[a];m.prototype[a]=function(){return v(b.apply(this._wrapped,arguments),this._chain)}});m.prototype.chain=function(){this._chain=
+true;return this};m.prototype.value=function(){return this._wrapped}}).call(this);

Added: www-releases/trunk/3.9.1/docs/_static/up-pressed.png
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_static/up-pressed.png?rev=290368&view=auto
==============================================================================
Binary file - no diff available.

Propchange: www-releases/trunk/3.9.1/docs/_static/up-pressed.png
------------------------------------------------------------------------------
    svn:mime-type = image/png

Added: www-releases/trunk/3.9.1/docs/_static/up.png
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_static/up.png?rev=290368&view=auto
==============================================================================
Binary file - no diff available.

Propchange: www-releases/trunk/3.9.1/docs/_static/up.png
------------------------------------------------------------------------------
    svn:mime-type = image/png

Added: www-releases/trunk/3.9.1/docs/_static/websupport.js
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/_static/websupport.js?rev=290368&view=auto
==============================================================================
--- www-releases/trunk/3.9.1/docs/_static/websupport.js (added)
+++ www-releases/trunk/3.9.1/docs/_static/websupport.js Thu Dec 22 14:04:03 2016
@@ -0,0 +1,808 @@
+/*
+ * websupport.js
+ * ~~~~~~~~~~~~~
+ *
+ * sphinx.websupport utilties for all documentation.
+ *
+ * :copyright: Copyright 2007-2014 by the Sphinx team, see AUTHORS.
+ * :license: BSD, see LICENSE for details.
+ *
+ */
+
+(function($) {
+  $.fn.autogrow = function() {
+    return this.each(function() {
+    var textarea = this;
+
+    $.fn.autogrow.resize(textarea);
+
+    $(textarea)
+      .focus(function() {
+        textarea.interval = setInterval(function() {
+          $.fn.autogrow.resize(textarea);
+        }, 500);
+      })
+      .blur(function() {
+        clearInterval(textarea.interval);
+      });
+    });
+  };
+
+  $.fn.autogrow.resize = function(textarea) {
+    var lineHeight = parseInt($(textarea).css('line-height'), 10);
+    var lines = textarea.value.split('\n');
+    var columns = textarea.cols;
+    var lineCount = 0;
+    $.each(lines, function() {
+      lineCount += Math.ceil(this.length / columns) || 1;
+    });
+    var height = lineHeight * (lineCount + 1);
+    $(textarea).css('height', height);
+  };
+})(jQuery);
+
+(function($) {
+  var comp, by;
+
+  function init() {
+    initEvents();
+    initComparator();
+  }
+
+  function initEvents() {
+    $('a.comment-close').live("click", function(event) {
+      event.preventDefault();
+      hide($(this).attr('id').substring(2));
+    });
+    $('a.vote').live("click", function(event) {
+      event.preventDefault();
+      handleVote($(this));
+    });
+    $('a.reply').live("click", function(event) {
+      event.preventDefault();
+      openReply($(this).attr('id').substring(2));
+    });
+    $('a.close-reply').live("click", function(event) {
+      event.preventDefault();
+      closeReply($(this).attr('id').substring(2));
+    });
+    $('a.sort-option').live("click", function(event) {
+      event.preventDefault();
+      handleReSort($(this));
+    });
+    $('a.show-proposal').live("click", function(event) {
+      event.preventDefault();
+      showProposal($(this).attr('id').substring(2));
+    });
+    $('a.hide-proposal').live("click", function(event) {
+      event.preventDefault();
+      hideProposal($(this).attr('id').substring(2));
+    });
+    $('a.show-propose-change').live("click", function(event) {
+      event.preventDefault();
+      showProposeChange($(this).attr('id').substring(2));
+    });
+    $('a.hide-propose-change').live("click", function(event) {
+      event.preventDefault();
+      hideProposeChange($(this).attr('id').substring(2));
+    });
+    $('a.accept-comment').live("click", function(event) {
+      event.preventDefault();
+      acceptComment($(this).attr('id').substring(2));
+    });
+    $('a.delete-comment').live("click", function(event) {
+      event.preventDefault();
+      deleteComment($(this).attr('id').substring(2));
+    });
+    $('a.comment-markup').live("click", function(event) {
+      event.preventDefault();
+      toggleCommentMarkupBox($(this).attr('id').substring(2));
+    });
+  }
+
+  /**
+   * Set comp, which is a comparator function used for sorting and
+   * inserting comments into the list.
+   */
+  function setComparator() {
+    // If the first three letters are "asc", sort in ascending order
+    // and remove the prefix.
+    if (by.substring(0,3) == 'asc') {
+      var i = by.substring(3);
+      comp = function(a, b) { return a[i] - b[i]; };
+    } else {
+      // Otherwise sort in descending order.
+      comp = function(a, b) { return b[by] - a[by]; };
+    }
+
+    // Reset link styles and format the selected sort option.
+    $('a.sel').attr('href', '#').removeClass('sel');
+    $('a.by' + by).removeAttr('href').addClass('sel');
+  }
+
+  /**
+   * Create a comp function. If the user has preferences stored in
+   * the sortBy cookie, use those, otherwise use the default.
+   */
+  function initComparator() {
+    by = 'rating'; // Default to sort by rating.
+    // If the sortBy cookie is set, use that instead.
+    if (document.cookie.length > 0) {
+      var start = document.cookie.indexOf('sortBy=');
+      if (start != -1) {
+        start = start + 7;
+        var end = document.cookie.indexOf(";", start);
+        if (end == -1) {
+          end = document.cookie.length;
+          by = unescape(document.cookie.substring(start, end));
+        }
+      }
+    }
+    setComparator();
+  }
+
+  /**
+   * Show a comment div.
+   */
+  function show(id) {
+    $('#ao' + id).hide();
+    $('#ah' + id).show();
+    var context = $.extend({id: id}, opts);
+    var popup = $(renderTemplate(popupTemplate, context)).hide();
+    popup.find('textarea[name="proposal"]').hide();
+    popup.find('a.by' + by).addClass('sel');
+    var form = popup.find('#cf' + id);
+    form.submit(function(event) {
+      event.preventDefault();
+      addComment(form);
+    });
+    $('#s' + id).after(popup);
+    popup.slideDown('fast', function() {
+      getComments(id);
+    });
+  }
+
+  /**
+   * Hide a comment div.
+   */
+  function hide(id) {
+    $('#ah' + id).hide();
+    $('#ao' + id).show();
+    var div = $('#sc' + id);
+    div.slideUp('fast', function() {
+      div.remove();
+    });
+  }
+
+  /**
+   * Perform an ajax request to get comments for a node
+   * and insert the comments into the comments tree.
+   */
+  function getComments(id) {
+    $.ajax({
+     type: 'GET',
+     url: opts.getCommentsURL,
+     data: {node: id},
+     success: function(data, textStatus, request) {
+       var ul = $('#cl' + id);
+       var speed = 100;
+       $('#cf' + id)
+         .find('textarea[name="proposal"]')
+         .data('source', data.source);
+
+       if (data.comments.length === 0) {
+         ul.html('<li>No comments yet.</li>');
+         ul.data('empty', true);
+       } else {
+         // If there are comments, sort them and put them in the list.
+         var comments = sortComments(data.comments);
+         speed = data.comments.length * 100;
+         appendComments(comments, ul);
+         ul.data('empty', false);
+       }
+       $('#cn' + id).slideUp(speed + 200);
+       ul.slideDown(speed);
+     },
+     error: function(request, textStatus, error) {
+       showError('Oops, there was a problem retrieving the comments.');
+     },
+     dataType: 'json'
+    });
+  }
+
+  /**
+   * Add a comment via ajax and insert the comment into the comment tree.
+   */
+  function addComment(form) {
+    var node_id = form.find('input[name="node"]').val();
+    var parent_id = form.find('input[name="parent"]').val();
+    var text = form.find('textarea[name="comment"]').val();
+    var proposal = form.find('textarea[name="proposal"]').val();
+
+    if (text == '') {
+      showError('Please enter a comment.');
+      return;
+    }
+
+    // Disable the form that is being submitted.
+    form.find('textarea,input').attr('disabled', 'disabled');
+
+    // Send the comment to the server.
+    $.ajax({
+      type: "POST",
+      url: opts.addCommentURL,
+      dataType: 'json',
+      data: {
+        node: node_id,
+        parent: parent_id,
+        text: text,
+        proposal: proposal
+      },
+      success: function(data, textStatus, error) {
+        // Reset the form.
+        if (node_id) {
+          hideProposeChange(node_id);
+        }
+        form.find('textarea')
+          .val('')
+          .add(form.find('input'))
+          .removeAttr('disabled');
+	var ul = $('#cl' + (node_id || parent_id));
+        if (ul.data('empty')) {
+          $(ul).empty();
+          ul.data('empty', false);
+        }
+        insertComment(data.comment);
+        var ao = $('#ao' + node_id);
+        ao.find('img').attr({'src': opts.commentBrightImage});
+        if (node_id) {
+          // if this was a "root" comment, remove the commenting box
+          // (the user can get it back by reopening the comment popup)
+          $('#ca' + node_id).slideUp();
+        }
+      },
+      error: function(request, textStatus, error) {
+        form.find('textarea,input').removeAttr('disabled');
+        showError('Oops, there was a problem adding the comment.');
+      }
+    });
+  }
+
+  /**
+   * Recursively append comments to the main comment list and children
+   * lists, creating the comment tree.
+   */
+  function appendComments(comments, ul) {
+    $.each(comments, function() {
+      var div = createCommentDiv(this);
+      ul.append($(document.createElement('li')).html(div));
+      appendComments(this.children, div.find('ul.comment-children'));
+      // To avoid stagnating data, don't store the comments children in data.
+      this.children = null;
+      div.data('comment', this);
+    });
+  }
+
+  /**
+   * After adding a new comment, it must be inserted in the correct
+   * location in the comment tree.
+   */
+  function insertComment(comment) {
+    var div = createCommentDiv(comment);
+
+    // To avoid stagnating data, don't store the comments children in data.
+    comment.children = null;
+    div.data('comment', comment);
+
+    var ul = $('#cl' + (comment.node || comment.parent));
+    var siblings = getChildren(ul);
+
+    var li = $(document.createElement('li'));
+    li.hide();
+
+    // Determine where in the parents children list to insert this comment.
+    for(i=0; i < siblings.length; i++) {
+      if (comp(comment, siblings[i]) <= 0) {
+        $('#cd' + siblings[i].id)
+          .parent()
+          .before(li.html(div));
+        li.slideDown('fast');
+        return;
+      }
+    }
+
+    // If we get here, this comment rates lower than all the others,
+    // or it is the only comment in the list.
+    ul.append(li.html(div));
+    li.slideDown('fast');
+  }
+
+  function acceptComment(id) {
+    $.ajax({
+      type: 'POST',
+      url: opts.acceptCommentURL,
+      data: {id: id},
+      success: function(data, textStatus, request) {
+        $('#cm' + id).fadeOut('fast');
+        $('#cd' + id).removeClass('moderate');
+      },
+      error: function(request, textStatus, error) {
+        showError('Oops, there was a problem accepting the comment.');
+      }
+    });
+  }
+
+  function deleteComment(id) {
+    $.ajax({
+      type: 'POST',
+      url: opts.deleteCommentURL,
+      data: {id: id},
+      success: function(data, textStatus, request) {
+        var div = $('#cd' + id);
+        if (data == 'delete') {
+          // Moderator mode: remove the comment and all children immediately
+          div.slideUp('fast', function() {
+            div.remove();
+          });
+          return;
+        }
+        // User mode: only mark the comment as deleted
+        div
+          .find('span.user-id:first')
+          .text('[deleted]').end()
+          .find('div.comment-text:first')
+          .text('[deleted]').end()
+          .find('#cm' + id + ', #dc' + id + ', #ac' + id + ', #rc' + id +
+                ', #sp' + id + ', #hp' + id + ', #cr' + id + ', #rl' + id)
+          .remove();
+        var comment = div.data('comment');
+        comment.username = '[deleted]';
+        comment.text = '[deleted]';
+        div.data('comment', comment);
+      },
+      error: function(request, textStatus, error) {
+        showError('Oops, there was a problem deleting the comment.');
+      }
+    });
+  }
+
+  function showProposal(id) {
+    $('#sp' + id).hide();
+    $('#hp' + id).show();
+    $('#pr' + id).slideDown('fast');
+  }
+
+  function hideProposal(id) {
+    $('#hp' + id).hide();
+    $('#sp' + id).show();
+    $('#pr' + id).slideUp('fast');
+  }
+
+  function showProposeChange(id) {
+    $('#pc' + id).hide();
+    $('#hc' + id).show();
+    var textarea = $('#pt' + id);
+    textarea.val(textarea.data('source'));
+    $.fn.autogrow.resize(textarea[0]);
+    textarea.slideDown('fast');
+  }
+
+  function hideProposeChange(id) {
+    $('#hc' + id).hide();
+    $('#pc' + id).show();
+    var textarea = $('#pt' + id);
+    textarea.val('').removeAttr('disabled');
+    textarea.slideUp('fast');
+  }
+
+  function toggleCommentMarkupBox(id) {
+    $('#mb' + id).toggle();
+  }
+
+  /** Handle when the user clicks on a sort by link. */
+  function handleReSort(link) {
+    var classes = link.attr('class').split(/\s+/);
+    for (var i=0; i<classes.length; i++) {
+      if (classes[i] != 'sort-option') {
+	by = classes[i].substring(2);
+      }
+    }
+    setComparator();
+    // Save/update the sortBy cookie.
+    var expiration = new Date();
+    expiration.setDate(expiration.getDate() + 365);
+    document.cookie= 'sortBy=' + escape(by) +
+                     ';expires=' + expiration.toUTCString();
+    $('ul.comment-ul').each(function(index, ul) {
+      var comments = getChildren($(ul), true);
+      comments = sortComments(comments);
+      appendComments(comments, $(ul).empty());
+    });
+  }
+
+  /**
+   * Function to process a vote when a user clicks an arrow.
+   */
+  function handleVote(link) {
+    if (!opts.voting) {
+      showError("You'll need to login to vote.");
+      return;
+    }
+
+    var id = link.attr('id');
+    if (!id) {
+      // Didn't click on one of the voting arrows.
+      return;
+    }
+    // If it is an unvote, the new vote value is 0,
+    // Otherwise it's 1 for an upvote, or -1 for a downvote.
+    var value = 0;
+    if (id.charAt(1) != 'u') {
+      value = id.charAt(0) == 'u' ? 1 : -1;
+    }
+    // The data to be sent to the server.
+    var d = {
+      comment_id: id.substring(2),
+      value: value
+    };
+
+    // Swap the vote and unvote links.
+    link.hide();
+    $('#' + id.charAt(0) + (id.charAt(1) == 'u' ? 'v' : 'u') + d.comment_id)
+      .show();
+
+    // The div the comment is displayed in.
+    var div = $('div#cd' + d.comment_id);
+    var data = div.data('comment');
+
+    // If this is not an unvote, and the other vote arrow has
+    // already been pressed, unpress it.
+    if ((d.value !== 0) && (data.vote === d.value * -1)) {
+      $('#' + (d.value == 1 ? 'd' : 'u') + 'u' + d.comment_id).hide();
+      $('#' + (d.value == 1 ? 'd' : 'u') + 'v' + d.comment_id).show();
+    }
+
+    // Update the comments rating in the local data.
+    data.rating += (data.vote === 0) ? d.value : (d.value - data.vote);
+    data.vote = d.value;
+    div.data('comment', data);
+
+    // Change the rating text.
+    div.find('.rating:first')
+      .text(data.rating + ' point' + (data.rating == 1 ? '' : 's'));
+
+    // Send the vote information to the server.
+    $.ajax({
+      type: "POST",
+      url: opts.processVoteURL,
+      data: d,
+      error: function(request, textStatus, error) {
+        showError('Oops, there was a problem casting that vote.');
+      }
+    });
+  }
+
+  /**
+   * Open a reply form used to reply to an existing comment.
+   */
+  function openReply(id) {
+    // Swap out the reply link for the hide link
+    $('#rl' + id).hide();
+    $('#cr' + id).show();
+
+    // Add the reply li to the children ul.
+    var div = $(renderTemplate(replyTemplate, {id: id})).hide();
+    $('#cl' + id)
+      .prepend(div)
+      // Setup the submit handler for the reply form.
+      .find('#rf' + id)
+      .submit(function(event) {
+        event.preventDefault();
+        addComment($('#rf' + id));
+        closeReply(id);
+      })
+      .find('input[type=button]')
+      .click(function() {
+        closeReply(id);
+      });
+    div.slideDown('fast', function() {
+      $('#rf' + id).find('textarea').focus();
+    });
+  }
+
+  /**
+   * Close the reply form opened with openReply.
+   */
+  function closeReply(id) {
+    // Remove the reply div from the DOM.
+    $('#rd' + id).slideUp('fast', function() {
+      $(this).remove();
+    });
+
+    // Swap out the hide link for the reply link
+    $('#cr' + id).hide();
+    $('#rl' + id).show();
+  }
+
+  /**
+   * Recursively sort a tree of comments using the comp comparator.
+   */
+  function sortComments(comments) {
+    comments.sort(comp);
+    $.each(comments, function() {
+      this.children = sortComments(this.children);
+    });
+    return comments;
+  }
+
+  /**
+   * Get the children comments from a ul. If recursive is true,
+   * recursively include childrens' children.
+   */
+  function getChildren(ul, recursive) {
+    var children = [];
+    ul.children().children("[id^='cd']")
+      .each(function() {
+        var comment = $(this).data('comment');
+        if (recursive)
+          comment.children = getChildren($(this).find('#cl' + comment.id), true);
+        children.push(comment);
+      });
+    return children;
+  }
+
+  /** Create a div to display a comment in. */
+  function createCommentDiv(comment) {
+    if (!comment.displayed && !opts.moderator) {
+      return $('<div class="moderate">Thank you!  Your comment will show up '
+               + 'once it is has been approved by a moderator.</div>');
+    }
+    // Prettify the comment rating.
+    comment.pretty_rating = comment.rating + ' point' +
+      (comment.rating == 1 ? '' : 's');
+    // Make a class (for displaying not yet moderated comments differently)
+    comment.css_class = comment.displayed ? '' : ' moderate';
+    // Create a div for this comment.
+    var context = $.extend({}, opts, comment);
+    var div = $(renderTemplate(commentTemplate, context));
+
+    // If the user has voted on this comment, highlight the correct arrow.
+    if (comment.vote) {
+      var direction = (comment.vote == 1) ? 'u' : 'd';
+      div.find('#' + direction + 'v' + comment.id).hide();
+      div.find('#' + direction + 'u' + comment.id).show();
+    }
+
+    if (opts.moderator || comment.text != '[deleted]') {
+      div.find('a.reply').show();
+      if (comment.proposal_diff)
+        div.find('#sp' + comment.id).show();
+      if (opts.moderator && !comment.displayed)
+        div.find('#cm' + comment.id).show();
+      if (opts.moderator || (opts.username == comment.username))
+        div.find('#dc' + comment.id).show();
+    }
+    return div;
+  }
+
+  /**
+   * A simple template renderer. Placeholders such as <%id%> are replaced
+   * by context['id'] with items being escaped. Placeholders such as <#id#>
+   * are not escaped.
+   */
+  function renderTemplate(template, context) {
+    var esc = $(document.createElement('div'));
+
+    function handle(ph, escape) {
+      var cur = context;
+      $.each(ph.split('.'), function() {
+        cur = cur[this];
+      });
+      return escape ? esc.text(cur || "").html() : cur;
+    }
+
+    return template.replace(/<([%#])([\w\.]*)\1>/g, function() {
+      return handle(arguments[2], arguments[1] == '%' ? true : false);
+    });
+  }
+
+  /** Flash an error message briefly. */
+  function showError(message) {
+    $(document.createElement('div')).attr({'class': 'popup-error'})
+      .append($(document.createElement('div'))
+               .attr({'class': 'error-message'}).text(message))
+      .appendTo('body')
+      .fadeIn("slow")
+      .delay(2000)
+      .fadeOut("slow");
+  }
+
+  /** Add a link the user uses to open the comments popup. */
+  $.fn.comment = function() {
+    return this.each(function() {
+      var id = $(this).attr('id').substring(1);
+      var count = COMMENT_METADATA[id];
+      var title = count + ' comment' + (count == 1 ? '' : 's');
+      var image = count > 0 ? opts.commentBrightImage : opts.commentImage;
+      var addcls = count == 0 ? ' nocomment' : '';
+      $(this)
+        .append(
+          $(document.createElement('a')).attr({
+            href: '#',
+            'class': 'sphinx-comment-open' + addcls,
+            id: 'ao' + id
+          })
+            .append($(document.createElement('img')).attr({
+              src: image,
+              alt: 'comment',
+              title: title
+            }))
+            .click(function(event) {
+              event.preventDefault();
+              show($(this).attr('id').substring(2));
+            })
+        )
+        .append(
+          $(document.createElement('a')).attr({
+            href: '#',
+            'class': 'sphinx-comment-close hidden',
+            id: 'ah' + id
+          })
+            .append($(document.createElement('img')).attr({
+              src: opts.closeCommentImage,
+              alt: 'close',
+              title: 'close'
+            }))
+            .click(function(event) {
+              event.preventDefault();
+              hide($(this).attr('id').substring(2));
+            })
+        );
+    });
+  };
+
+  var opts = {
+    processVoteURL: '/_process_vote',
+    addCommentURL: '/_add_comment',
+    getCommentsURL: '/_get_comments',
+    acceptCommentURL: '/_accept_comment',
+    deleteCommentURL: '/_delete_comment',
+    commentImage: '/static/_static/comment.png',
+    closeCommentImage: '/static/_static/comment-close.png',
+    loadingImage: '/static/_static/ajax-loader.gif',
+    commentBrightImage: '/static/_static/comment-bright.png',
+    upArrow: '/static/_static/up.png',
+    downArrow: '/static/_static/down.png',
+    upArrowPressed: '/static/_static/up-pressed.png',
+    downArrowPressed: '/static/_static/down-pressed.png',
+    voting: false,
+    moderator: false
+  };
+
+  if (typeof COMMENT_OPTIONS != "undefined") {
+    opts = jQuery.extend(opts, COMMENT_OPTIONS);
+  }
+
+  var popupTemplate = '\
+    <div class="sphinx-comments" id="sc<%id%>">\
+      <p class="sort-options">\
+        Sort by:\
+        <a href="#" class="sort-option byrating">best rated</a>\
+        <a href="#" class="sort-option byascage">newest</a>\
+        <a href="#" class="sort-option byage">oldest</a>\
+      </p>\
+      <div class="comment-header">Comments</div>\
+      <div class="comment-loading" id="cn<%id%>">\
+        loading comments... <img src="<%loadingImage%>" alt="" /></div>\
+      <ul id="cl<%id%>" class="comment-ul"></ul>\
+      <div id="ca<%id%>">\
+      <p class="add-a-comment">Add a comment\
+        (<a href="#" class="comment-markup" id="ab<%id%>">markup</a>):</p>\
+      <div class="comment-markup-box" id="mb<%id%>">\
+        reStructured text markup: <i>*emph*</i>, <b>**strong**</b>, \
+        <tt>``code``</tt>, \
+        code blocks: <tt>::</tt> and an indented block after blank line</div>\
+      <form method="post" id="cf<%id%>" class="comment-form" action="">\
+        <textarea name="comment" cols="80"></textarea>\
+        <p class="propose-button">\
+          <a href="#" id="pc<%id%>" class="show-propose-change">\
+            Propose a change ▹\
+          </a>\
+          <a href="#" id="hc<%id%>" class="hide-propose-change">\
+            Propose a change ▿\
+          </a>\
+        </p>\
+        <textarea name="proposal" id="pt<%id%>" cols="80"\
+                  spellcheck="false"></textarea>\
+        <input type="submit" value="Add comment" />\
+        <input type="hidden" name="node" value="<%id%>" />\
+        <input type="hidden" name="parent" value="" />\
+      </form>\
+      </div>\
+    </div>';
+
+  var commentTemplate = '\
+    <div id="cd<%id%>" class="sphinx-comment<%css_class%>">\
+      <div class="vote">\
+        <div class="arrow">\
+          <a href="#" id="uv<%id%>" class="vote" title="vote up">\
+            <img src="<%upArrow%>" />\
+          </a>\
+          <a href="#" id="uu<%id%>" class="un vote" title="vote up">\
+            <img src="<%upArrowPressed%>" />\
+          </a>\
+        </div>\
+        <div class="arrow">\
+          <a href="#" id="dv<%id%>" class="vote" title="vote down">\
+            <img src="<%downArrow%>" id="da<%id%>" />\
+          </a>\
+          <a href="#" id="du<%id%>" class="un vote" title="vote down">\
+            <img src="<%downArrowPressed%>" />\
+          </a>\
+        </div>\
+      </div>\
+      <div class="comment-content">\
+        <p class="tagline comment">\
+          <span class="user-id"><%username%></span>\
+          <span class="rating"><%pretty_rating%></span>\
+          <span class="delta"><%time.delta%></span>\
+        </p>\
+        <div class="comment-text comment"><#text#></div>\
+        <p class="comment-opts comment">\
+          <a href="#" class="reply hidden" id="rl<%id%>">reply ▹</a>\
+          <a href="#" class="close-reply" id="cr<%id%>">reply ▿</a>\
+          <a href="#" id="sp<%id%>" class="show-proposal">proposal ▹</a>\
+          <a href="#" id="hp<%id%>" class="hide-proposal">proposal ▿</a>\
+          <a href="#" id="dc<%id%>" class="delete-comment hidden">delete</a>\
+          <span id="cm<%id%>" class="moderation hidden">\
+            <a href="#" id="ac<%id%>" class="accept-comment">accept</a>\
+          </span>\
+        </p>\
+        <pre class="proposal" id="pr<%id%>">\
+<#proposal_diff#>\
+        </pre>\
+          <ul class="comment-children" id="cl<%id%>"></ul>\
+        </div>\
+        <div class="clearleft"></div>\
+      </div>\
+    </div>';
+
+  var replyTemplate = '\
+    <li>\
+      <div class="reply-div" id="rd<%id%>">\
+        <form id="rf<%id%>">\
+          <textarea name="comment" cols="80"></textarea>\
+          <input type="submit" value="Add reply" />\
+          <input type="button" value="Cancel" />\
+          <input type="hidden" name="parent" value="<%id%>" />\
+          <input type="hidden" name="node" value="" />\
+        </form>\
+      </div>\
+    </li>';
+
+  $(document).ready(function() {
+    init();
+  });
+})(jQuery);
+
+$(document).ready(function() {
+  // add comment anchors for all paragraphs that are commentable
+  $('.sphinx-has-comment').comment();
+
+  // highlight search words in search results
+  $("div.context").each(function() {
+    var params = $.getQueryParameters();
+    var terms = (params.q) ? params.q[0].split(/\s+/) : [];
+    var result = $(this);
+    $.each(terms, function() {
+      result.highlightText(this.toLowerCase(), 'highlighted');
+    });
+  });
+
+  // directly open comment window if requested
+  var anchor = document.location.hash;
+  if (anchor.substring(0, 9) == '#comment-') {
+    $('#ao' + anchor.substring(9)).click();
+    document.location.hash = '#s' + anchor.substring(9);
+  }
+});

Added: www-releases/trunk/3.9.1/docs/genindex.html
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/genindex.html?rev=290368&view=auto
==============================================================================
--- www-releases/trunk/3.9.1/docs/genindex.html (added)
+++ www-releases/trunk/3.9.1/docs/genindex.html Thu Dec 22 14:04:03 2016
@@ -0,0 +1,3130 @@
+
+
+<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN"
+  "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd">
+
+
+<html xmlns="http://www.w3.org/1999/xhtml">
+  <head>
+    <meta http-equiv="Content-Type" content="text/html; charset=utf-8" />
+    
+    <title>Index — LLVM 3.9 documentation</title>
+    
+    <link rel="stylesheet" href="_static/llvm-theme.css" type="text/css" />
+    <link rel="stylesheet" href="_static/pygments.css" type="text/css" />
+    
+    <script type="text/javascript">
+      var DOCUMENTATION_OPTIONS = {
+        URL_ROOT:    './',
+        VERSION:     '3.9',
+        COLLAPSE_INDEX: false,
+        FILE_SUFFIX: '.html',
+        HAS_SOURCE:  true
+      };
+    </script>
+    <script type="text/javascript" src="_static/jquery.js"></script>
+    <script type="text/javascript" src="_static/underscore.js"></script>
+    <script type="text/javascript" src="_static/doctools.js"></script>
+    <link rel="top" title="LLVM 3.9 documentation" href="index.html" />
+<style type="text/css">
+  table.right { float: right; margin-left: 20px; }
+  table.right td { border: 1px solid #ccc; }
+</style>
+
+  </head>
+  <body>
+<div class="logo">
+  <a href="index.html">
+    <img src="_static/logo.png"
+         alt="LLVM Logo" width="250" height="88"/></a>
+</div>
+
+    <div class="related">
+      <h3>Navigation</h3>
+      <ul>
+        <li class="right" style="margin-right: 10px">
+          <a href="#" title="General Index"
+             accesskey="I">index</a></li>
+  <li><a href="http://llvm.org/">LLVM Home</a> | </li>
+  <li><a href="index.html">Documentation</a>»</li>
+ 
+      </ul>
+    </div>
+
+
+    <div class="document">
+      <div class="documentwrapper">
+          <div class="body">
+            
+
+<h1 id="index">Index</h1>
+
+<div class="genindex-jumpbox">
+ <a href="#Symbols"><strong>Symbols</strong></a>
+ | <a href="#C"><strong>C</strong></a>
+ | <a href="#L"><strong>L</strong></a>
+ | <a href="#T"><strong>T</strong></a>
+ 
+</div>
+<h2 id="Symbols">Symbols</h2>
+<table style="width: 100%" class="indextable genindextable"><tr>
+  <td style="width: 33%" valign="top"><dl>
+      
+  <dt>
+    --check-prefix prefix
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/FileCheck.html#cmdoption--check-prefix">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --check-prefixes prefix1,prefix2,...
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/FileCheck.html#cmdoption--check-prefixes">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --config-prefix=NAME
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--config-prefix">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --debug
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--debug">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --debug-syms, -a
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm--debug-syms">llvm-nm command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --defined-only
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm--defined-only">llvm-nm command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --disable-excess-fp-precision
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption--disable-excess-fp-precision">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --disable-fp-elim
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption--disable-fp-elim">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --dynamic, -D
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm--dynamic">llvm-nm command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --enable-no-infs-fp-math
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption--enable-no-infs-fp-math">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --enable-no-nans-fp-math
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption--enable-no-nans-fp-math">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --enable-unsafe-fp-math
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption--enable-unsafe-fp-math">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --extern-only, -g
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm--extern-only">llvm-nm command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --format=format, -f format
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm--format">llvm-nm command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --help
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-gcov--help">llvm-cov-gcov command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --implicit-check-not check-pattern
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/FileCheck.html#cmdoption--implicit-check-not">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --input-file filename
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/FileCheck.html#cmdoption--input-file">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --load=<dso_path>
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption--load">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --match-full-lines
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/FileCheck.html#cmdoption--match-full-lines">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --max-tests=N
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--max-tests">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --max-time=N
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--max-time">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --no-progress-bar
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--no-progress-bar">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --no-sort, -p
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm--no-sort">llvm-nm command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --numeric-sort, -n, -v
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm--numeric-sort">llvm-nm command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --path=PATH
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--path">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --print-file-name, -A, -o
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm--print-file-name">llvm-nm command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --print-machineinstrs
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption--print-machineinstrs">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --print-size, -S
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm--print-size">llvm-nm command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --radix=RADIX, -t
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm--radix">llvm-nm command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --regalloc=<allocator>
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption--regalloc">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --show-suites
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--show-suites">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --show-tests
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--show-tests">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --show-unsupported
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--show-unsupported">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --show-xfail
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--show-xfail">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --shuffle
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--shuffle">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --size-sort
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm--size-sort">llvm-nm command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --spiller=<spiller>
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption--spiller">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --stats
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption--stats">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --strict-whitespace
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/FileCheck.html#cmdoption--strict-whitespace">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --time-passes
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption--time-passes">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --time-tests
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--time-tests">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --undefined-only, -u
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm--undefined-only">llvm-nm command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --vg
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--vg">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --vg-arg=ARG
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--vg-arg">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --vg-leak
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--vg-leak">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    --x86-asm-syntax=[att|intel]
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption--x86-asm-syntax">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -a, --all-blocks
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-gcov-a">llvm-cov-gcov command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -a, --show-all
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption-a">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -all-functions
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-show-all-functions">llvm-profdata-show command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -arch=<name>
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-report-arch">llvm-cov-report command line option</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-arch">llvm-cov-show command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -asmparsernum N
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-asmparsernum">tblgen command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -asmwriternum N
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-asmwriternum">tblgen command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -B    (default)
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm-B">llvm-nm command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -b, --branch-probabilities
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-gcov-b">llvm-cov-gcov command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -binary (default)
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-merge-binary">llvm-profdata-merge command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -c, --branch-counts
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-gcov-c">llvm-cov-gcov command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -class className
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-class">tblgen command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -code-model=model
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-code-model">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -counts
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-show-counts">llvm-profdata-show command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -d
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-link.html#cmdoption-d">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -D NAME, -D NAME=VALUE, --param NAME, --param NAME=VALUE
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption-D">command line option</a>, <a href="CommandGuide/lit.html#cmdoption-D">[1]</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -debug
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-debug">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -debug-dump=section
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-dwarfdump.html#cmdoption-debug-dump">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -default-arch
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-symbolizer.html#cmdoption-default-arch">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -demangle
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-symbolizer.html#cmdoption-demangle">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -disable-excess-fp-precision
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-disable-excess-fp-precision">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -disable-inlining
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-disable-inlining">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -disable-opt
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-disable-opt">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -disable-post-RA-scheduler
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-disable-post-RA-scheduler">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -disable-spill-fusing
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-disable-spill-fusing">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -dsym-hint=<path/to/file.dSYM>
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-symbolizer.html#cmdoption-dsym-hint">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -dump
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-bcanalyzer.html#cmdoption-llvm-bcanalyzer-dump">llvm-bcanalyzer command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -dyn-symbols
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-dyn-symbols">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -dynamic-table
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-dynamic-table">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -elf-section-groups, -g
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-elf-section-groups">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -enable-no-infs-fp-math
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-enable-no-infs-fp-math">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -enable-no-nans-fp-math
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-enable-no-nans-fp-math">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -enable-unsafe-fp-math
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-enable-unsafe-fp-math">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -expand-relocs
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-expand-relocs">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -f
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-f">command line option</a>, <a href="CommandGuide/llvm-link.html#cmdoption-f">[1]</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -f, --function-summaries
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-gcov-f">llvm-cov-gcov command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -fake-argv0=executable
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-fake-argv0">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -file-headers, -h
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-file-headers">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -filetype=<output file type>
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption-filetype">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -force-interpreter={false,true}
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-force-interpreter">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -format=<FORMAT>
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-format">llvm-cov-show command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -function=string
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-show-function">llvm-profdata-show command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -functions=[none|short|linkage]
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-symbolizer.html#cmdoption-functions">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -gcc
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-merge-gcc">llvm-profdata-merge command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -gen-asm-matcher
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-asm-matcher">tblgen command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -gen-asm-writer
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-asm-writer">tblgen command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -gen-dag-isel
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-dag-isel">tblgen command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -gen-dfa-packetizer
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-dfa-packetizer">tblgen command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -gen-disassembler
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-disassembler">tblgen command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -gen-emitter
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-emitter">tblgen command line option</a>
+  </dt>
+
+      </dl></dd>
+  </dl></td>
+  <td style="width: 33%" valign="top"><dl>
+      
+  <dt>
+    -gen-enhanced-disassembly-info
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-enhanced-disassembly-info">tblgen command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -gen-fast-isel
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-fast-isel">tblgen command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -gen-instr-info
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-instr-info">tblgen command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -gen-intrinsic
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-intrinsic">tblgen command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -gen-pseudo-lowering
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-pseudo-lowering">tblgen command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -gen-register-info
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-register-info">tblgen command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -gen-subtarget
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-subtarget">tblgen command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -gen-tgt-intrinsic
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-tgt-intrinsic">tblgen command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -h, --help
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption-h">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -help
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/FileCheck.html#cmdoption-help">command line option</a>, <a href="CommandGuide/llvm-readobj.html#cmdoption-help">[1]</a>, <a href="CommandGuide/opt.html#cmdoption-help">[2]</a>, <a href="CommandGuide/llc.html#cmdoption-help">[3]</a>, <a href="CommandGuide/lli.html#cmdoption-help">[4]</a>, <a href="CommandGuide/llvm-link.html#cmdoption-help">[5]</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-bcanalyzer.html#cmdoption-llvm-bcanalyzer-help">llvm-bcanalyzer command line option</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm-help">llvm-nm command line option</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-merge-help">llvm-profdata-merge command line option</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-show-help">llvm-profdata-show command line option</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-help">tblgen command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -I directory
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-I">tblgen command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -inlining
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-symbolizer.html#cmdoption-inlining">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -input-files=path, -f=path
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-merge-input-files">llvm-profdata-merge command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -instr (default)
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-merge-instr">llvm-profdata-merge command line option</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-show-instr">llvm-profdata-show command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -j N, --threads=N
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption-j">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -jit-enable-eh
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-jit-enable-eh">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -join-liveintervals
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-join-liveintervals">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -l, --long-file-names
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-gcov-l">llvm-cov-gcov command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -line-coverage-gt=<N>
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-line-coverage-gt">llvm-cov-show command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -line-coverage-lt=<N>
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-line-coverage-lt">llvm-cov-show command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -load=<plugin>
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-load">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -load=pluginfilename
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-load">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -march=<arch>
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption-march">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -march=arch
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-march">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -mattr=a1,+a2,-a3,...
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption-mattr">command line option</a>, <a href="CommandGuide/lli.html#cmdoption-mattr">[1]</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -mcpu=<cpuname>
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption-mcpu">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -mcpu=cpuname
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-mcpu">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -meabi=[default|gnu|4|5]
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption-meabi">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -mtriple=<target triple>
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption-mtriple">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -mtriple=target triple
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-mtriple">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -n, --no-output
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-gcov-n">llvm-cov-gcov command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -name-regex=<PATTERN>
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-name-regex">llvm-cov-show command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -name=<NAME>
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-name">llvm-cov-show command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -needed-libs
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-needed-libs">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -nodetails
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-bcanalyzer.html#cmdoption-llvm-bcanalyzer-nodetails">llvm-bcanalyzer command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -nozero-initialized-in-bss
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-nozero-initialized-in-bss">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -o <filename>
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-o">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -o filename
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-stress.html#cmdoption-o">command line option</a>, <a href="CommandGuide/llvm-link.html#cmdoption-o">[1]</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-o">tblgen command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -o=<DIR|FILE>, --object-directory=<DIR>, --object-file=<FILE>
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-gcov-o">llvm-cov-gcov command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -O=uint
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption-O">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -obj
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-symbolizer.html#cmdoption-obj">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -output-dir=PATH
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-output-dir">llvm-cov-show command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -output=output, -o=output
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-merge-output">llvm-profdata-merge command line option</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-show-output">llvm-profdata-show command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -P
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm-P">llvm-nm command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -p
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-p">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -p, --preserve-paths
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-gcov-p">llvm-cov-gcov command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -pre-RA-sched=scheduler
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-pre-RA-sched">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -pretty-print
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-symbolizer.html#cmdoption-pretty-print">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -print-address
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-symbolizer.html#cmdoption-print-address">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -print-enums
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-print-enums">tblgen command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -print-records
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-print-records">tblgen command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -print-sets
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-print-sets">tblgen command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -program-headers
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-program-headers">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -q, --quiet
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption-q">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -regalloc=allocator
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-regalloc">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -region-coverage-gt=<N>
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-region-coverage-gt">llvm-cov-show command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -region-coverage-lt=<N>
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-region-coverage-lt">llvm-cov-show command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -relocation-model=model
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-relocation-model">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -relocations, -r
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-relocations">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -S
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-S">command line option</a>, <a href="CommandGuide/llvm-link.html#cmdoption-S">[1]</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -s, --succinct
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption-s">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -sample
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-merge-sample">llvm-profdata-merge command line option</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-show-sample">llvm-profdata-show command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -section-data, -sd
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-section-data">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -section-relocations, -sr
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-section-relocations">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -section-symbols, -st
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-section-symbols">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -sections, -s
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-sections">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -seed seed
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-stress.html#cmdoption-seed">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -show-expansions
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-show-expansions">llvm-cov-show command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -show-instantiations
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-show-instantiations">llvm-cov-show command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -show-line-counts
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-show-line-counts">llvm-cov-show command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -show-line-counts-or-regions
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-show-line-counts-or-regions">llvm-cov-show command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -show-regions
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-show-regions">llvm-cov-show command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -size size
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-stress.html#cmdoption-size">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -soft-float
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-soft-float">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -sparse[=true|false]
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-merge-sparse">llvm-profdata-merge command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -spiller
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-spiller">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -stats
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-stats">command line option</a>, <a href="CommandGuide/lli.html#cmdoption-stats">[1]</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -strip-debug
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-strip-debug">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -symbols, -t
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-symbols">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -text
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-merge-text">llvm-profdata-merge command line option</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-show-text">llvm-profdata-show command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -time-passes
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-time-passes">command line option</a>, <a href="CommandGuide/lli.html#cmdoption-time-passes">[1]</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -u, --unconditional-branches
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-gcov-u">llvm-cov-gcov command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -unwind, -u
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-unwind">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -use-color[=VALUE]
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-report-use-color">llvm-cov-report command line option</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-use-color">llvm-cov-show command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -use-symbol-table
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-symbolizer.html#cmdoption-use-symbol-table">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -v
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-link.html#cmdoption-v">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -v, --verbose
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption-v">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -verify
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-bcanalyzer.html#cmdoption-llvm-bcanalyzer-verify">llvm-bcanalyzer command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -verify-each
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-verify-each">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -version
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/FileCheck.html#cmdoption-version">command line option</a>, <a href="CommandGuide/llvm-readobj.html#cmdoption-version">[1]</a>, <a href="CommandGuide/lli.html#cmdoption-version">[2]</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-gcov-version">llvm-cov-gcov command line option</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-version">tblgen command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -weighted-input=weight,filename
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-merge-weighted-input">llvm-profdata-merge command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -x86-asm-syntax=syntax
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-x86-asm-syntax">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -Xdemangler=<TOOL>|<TOOL-OPTION>
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-Xdemangler">llvm-cov-show command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -{passname}
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-">command line option</a>
+  </dt>
+
+      </dl></dd>
+  </dl></td>
+</tr></table>
+
+<h2 id="C">C</h2>
+<table style="width: 100%" class="indextable genindextable"><tr>
+  <td style="width: 33%" valign="top"><dl>
+      
+  <dt>
+    command line option
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/FileCheck.html#cmdoption--check-prefix">--check-prefix prefix</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/FileCheck.html#cmdoption--check-prefixes">--check-prefixes prefix1,prefix2,...</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--config-prefix">--config-prefix=NAME</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--debug">--debug</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption--disable-excess-fp-precision">--disable-excess-fp-precision</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption--disable-fp-elim">--disable-fp-elim</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption--enable-no-infs-fp-math">--enable-no-infs-fp-math</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption--enable-no-nans-fp-math">--enable-no-nans-fp-math</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption--enable-unsafe-fp-math">--enable-unsafe-fp-math</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/FileCheck.html#cmdoption--implicit-check-not">--implicit-check-not check-pattern</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/FileCheck.html#cmdoption--input-file">--input-file filename</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption--load">--load=<dso_path></a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/FileCheck.html#cmdoption--match-full-lines">--match-full-lines</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--max-tests">--max-tests=N</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--max-time">--max-time=N</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--no-progress-bar">--no-progress-bar</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--path">--path=PATH</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption--print-machineinstrs">--print-machineinstrs</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption--regalloc">--regalloc=<allocator></a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--show-suites">--show-suites</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--show-tests">--show-tests</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--show-unsupported">--show-unsupported</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--show-xfail">--show-xfail</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--shuffle">--shuffle</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption--spiller">--spiller=<spiller></a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption--stats">--stats</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/FileCheck.html#cmdoption--strict-whitespace">--strict-whitespace</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption--time-passes">--time-passes</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--time-tests">--time-tests</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--vg">--vg</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--vg-arg">--vg-arg=ARG</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--vg-leak">--vg-leak</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption--x86-asm-syntax">--x86-asm-syntax=[att|intel]</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption-D">-D NAME, -D NAME=VALUE, --param NAME, --param NAME=VALUE</a>, <a href="CommandGuide/lit.html#cmdoption-D">[1]</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption-O">-O=uint</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-S">-S</a>, <a href="CommandGuide/llvm-link.html#cmdoption-S">[1]</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption-a">-a, --show-all</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-code-model">-code-model=model</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-link.html#cmdoption-d">-d</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-debug">-debug</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-dwarfdump.html#cmdoption-debug-dump">-debug-dump=section</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-symbolizer.html#cmdoption-default-arch">-default-arch</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-symbolizer.html#cmdoption-demangle">-demangle</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-disable-excess-fp-precision">-disable-excess-fp-precision</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-disable-inlining">-disable-inlining</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-disable-opt">-disable-opt</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-disable-post-RA-scheduler">-disable-post-RA-scheduler</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-disable-spill-fusing">-disable-spill-fusing</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-symbolizer.html#cmdoption-dsym-hint">-dsym-hint=<path/to/file.dSYM></a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-dyn-symbols">-dyn-symbols</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-dynamic-table">-dynamic-table</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-elf-section-groups">-elf-section-groups, -g</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-enable-no-infs-fp-math">-enable-no-infs-fp-math</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-enable-no-nans-fp-math">-enable-no-nans-fp-math</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-enable-unsafe-fp-math">-enable-unsafe-fp-math</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-expand-relocs">-expand-relocs</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-f">-f</a>, <a href="CommandGuide/llvm-link.html#cmdoption-f">[1]</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-fake-argv0">-fake-argv0=executable</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-file-headers">-file-headers, -h</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption-filetype">-filetype=<output file type></a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-force-interpreter">-force-interpreter={false,true}</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-symbolizer.html#cmdoption-functions">-functions=[none|short|linkage]</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption-h">-h, --help</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/FileCheck.html#cmdoption-help">-help</a>, <a href="CommandGuide/llvm-readobj.html#cmdoption-help">[1]</a>, <a href="CommandGuide/opt.html#cmdoption-help">[2]</a>, <a href="CommandGuide/llc.html#cmdoption-help">[3]</a>, <a href="CommandGuide/lli.html#cmdoption-help">[4]</a>, <a href="CommandGuide/llvm-link.html#cmdoption-help">[5]</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-symbolizer.html#cmdoption-inlining">-inlining</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption-j">-j N, --threads=N</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-jit-enable-eh">-jit-enable-eh</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-join-liveintervals">-join-liveintervals</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-load">-load=<plugin></a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-load">-load=pluginfilename</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption-march">-march=<arch></a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-march">-march=arch</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption-mattr">-mattr=a1,+a2,-a3,...</a>, <a href="CommandGuide/lli.html#cmdoption-mattr">[1]</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption-mcpu">-mcpu=<cpuname></a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-mcpu">-mcpu=cpuname</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption-meabi">-meabi=[default|gnu|4|5]</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption-mtriple">-mtriple=<target triple></a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-mtriple">-mtriple=target triple</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-needed-libs">-needed-libs</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-nozero-initialized-in-bss">-nozero-initialized-in-bss</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-o">-o <filename></a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-stress.html#cmdoption-o">-o filename</a>, <a href="CommandGuide/llvm-link.html#cmdoption-o">[1]</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-symbolizer.html#cmdoption-obj">-obj</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-p">-p</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-pre-RA-sched">-pre-RA-sched=scheduler</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-symbolizer.html#cmdoption-pretty-print">-pretty-print</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-symbolizer.html#cmdoption-print-address">-print-address</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-program-headers">-program-headers</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption-q">-q, --quiet</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-regalloc">-regalloc=allocator</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-relocation-model">-relocation-model=model</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-relocations">-relocations, -r</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption-s">-s, --succinct</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-section-data">-section-data, -sd</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-section-relocations">-section-relocations, -sr</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-section-symbols">-section-symbols, -st</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-sections">-sections, -s</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-stress.html#cmdoption-seed">-seed seed</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-stress.html#cmdoption-size">-size size</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-soft-float">-soft-float</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-spiller">-spiller</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-stats">-stats</a>, <a href="CommandGuide/lli.html#cmdoption-stats">[1]</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-strip-debug">-strip-debug</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-symbols">-symbols, -t</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-time-passes">-time-passes</a>, <a href="CommandGuide/lli.html#cmdoption-time-passes">[1]</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-unwind">-unwind, -u</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-symbolizer.html#cmdoption-use-symbol-table">-use-symbol-table</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-link.html#cmdoption-v">-v</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption-v">-v, --verbose</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-verify-each">-verify-each</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/FileCheck.html#cmdoption-version">-version</a>, <a href="CommandGuide/llvm-readobj.html#cmdoption-version">[1]</a>, <a href="CommandGuide/lli.html#cmdoption-version">[2]</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/lli.html#cmdoption-x86-asm-syntax">-x86-asm-syntax=syntax</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-">-{passname}</a>
+  </dt>
+
+      </dl></dd>
+  </dl></td>
+</tr></table>
+
+<h2 id="L">L</h2>
+<table style="width: 100%" class="indextable genindextable"><tr>
+  <td style="width: 33%" valign="top"><dl>
+      
+  <dt>
+    llvm-bcanalyzer command line option
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-bcanalyzer.html#cmdoption-llvm-bcanalyzer-dump">-dump</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-bcanalyzer.html#cmdoption-llvm-bcanalyzer-help">-help</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-bcanalyzer.html#cmdoption-llvm-bcanalyzer-nodetails">-nodetails</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-bcanalyzer.html#cmdoption-llvm-bcanalyzer-verify">-verify</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    llvm-cov-gcov command line option
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-gcov--help">--help</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-gcov-a">-a, --all-blocks</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-gcov-b">-b, --branch-probabilities</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-gcov-c">-c, --branch-counts</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-gcov-f">-f, --function-summaries</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-gcov-l">-l, --long-file-names</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-gcov-n">-n, --no-output</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-gcov-o">-o=<DIR|FILE>, --object-directory=<DIR>, --object-file=<FILE></a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-gcov-p">-p, --preserve-paths</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-gcov-u">-u, --unconditional-branches</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-gcov-version">-version</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    llvm-cov-report command line option
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-report-arch">-arch=<name></a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-report-use-color">-use-color[=VALUE]</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    llvm-cov-show command line option
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-Xdemangler">-Xdemangler=<TOOL>|<TOOL-OPTION></a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-arch">-arch=<name></a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-format">-format=<FORMAT></a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-line-coverage-gt">-line-coverage-gt=<N></a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-line-coverage-lt">-line-coverage-lt=<N></a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-name-regex">-name-regex=<PATTERN></a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-name">-name=<NAME></a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-output-dir">-output-dir=PATH</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-region-coverage-gt">-region-coverage-gt=<N></a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-region-coverage-lt">-region-coverage-lt=<N></a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-show-expansions">-show-expansions</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-show-instantiations">-show-instantiations</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-show-line-counts">-show-line-counts</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-show-line-counts-or-regions">-show-line-counts-or-regions</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-show-regions">-show-regions</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-llvm-cov-show-use-color">-use-color[=VALUE]</a>
+  </dt>
+
+      </dl></dd>
+  </dl></td>
+  <td style="width: 33%" valign="top"><dl>
+      
+  <dt>
+    llvm-nm command line option
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm--debug-syms">--debug-syms, -a</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm--defined-only">--defined-only</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm--dynamic">--dynamic, -D</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm--extern-only">--extern-only, -g</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm--format">--format=format, -f format</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm--no-sort">--no-sort, -p</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm--numeric-sort">--numeric-sort, -n, -v</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm--print-file-name">--print-file-name, -A, -o</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm--print-size">--print-size, -S</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm--radix">--radix=RADIX, -t</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm--size-sort">--size-sort</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm--undefined-only">--undefined-only, -u</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm-B">-B    (default)</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm-P">-P</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-nm.html#cmdoption-llvm-nm-help">-help</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    llvm-profdata-merge command line option
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-merge-binary">-binary (default)</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-merge-gcc">-gcc</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-merge-help">-help</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-merge-input-files">-input-files=path, -f=path</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-merge-instr">-instr (default)</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-merge-output">-output=output, -o=output</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-merge-sample">-sample</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-merge-sparse">-sparse[=true|false]</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-merge-text">-text</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-merge-weighted-input">-weighted-input=weight,filename</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    llvm-profdata-show command line option
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-show-all-functions">-all-functions</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-show-counts">-counts</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-show-function">-function=string</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-show-help">-help</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-show-instr">-instr (default)</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-show-output">-output=output, -o=output</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-show-sample">-sample</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-profdata.html#cmdoption-llvm-profdata-show-text">-text</a>
+  </dt>
+
+      </dl></dd>
+  </dl></td>
+</tr></table>
+
+<h2 id="T">T</h2>
+<table style="width: 100%" class="indextable genindextable"><tr>
+  <td style="width: 33%" valign="top"><dl>
+      
+  <dt>
+    tblgen command line option
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-I">-I directory</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-asmparsernum">-asmparsernum N</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-asmwriternum">-asmwriternum N</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-class">-class className</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-asm-matcher">-gen-asm-matcher</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-asm-writer">-gen-asm-writer</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-dag-isel">-gen-dag-isel</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-dfa-packetizer">-gen-dfa-packetizer</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-disassembler">-gen-disassembler</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-emitter">-gen-emitter</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-enhanced-disassembly-info">-gen-enhanced-disassembly-info</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-fast-isel">-gen-fast-isel</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-instr-info">-gen-instr-info</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-intrinsic">-gen-intrinsic</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-pseudo-lowering">-gen-pseudo-lowering</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-register-info">-gen-register-info</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-subtarget">-gen-subtarget</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-gen-tgt-intrinsic">-gen-tgt-intrinsic</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-help">-help</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-o">-o filename</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-print-enums">-print-enums</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-print-records">-print-records</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-print-sets">-print-sets</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-version">-version</a>
+  </dt>
+
+      </dl></dd>
+  </dl></td>
+</tr></table>
+
+
+
+          </div>
+      </div>
+      <div class="clearer"></div>
+    </div>
+    <div class="related">
+      <h3>Navigation</h3>
+      <ul>
+        <li class="right" style="margin-right: 10px">
+          <a href="#" title="General Index"
+             >index</a></li>
+  <li><a href="http://llvm.org/">LLVM Home</a> | </li>
+  <li><a href="index.html">Documentation</a>»</li>
+ 
+      </ul>
+    </div>
+    <div class="footer">
+        © Copyright 2003-2016, LLVM Project.
+      Last updated on 2016-12-21.
+      Created using <a href="http://sphinx-doc.org/">Sphinx</a> 1.2.2.
+    </div>
+  </body>
+</html>
\ No newline at end of file

Added: www-releases/trunk/3.9.1/docs/index.html
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/index.html?rev=290368&view=auto
==============================================================================
--- www-releases/trunk/3.9.1/docs/index.html (added)
+++ www-releases/trunk/3.9.1/docs/index.html Thu Dec 22 14:04:03 2016
@@ -0,0 +1,391 @@
+
+<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN"
+  "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd">
+
+
+<html xmlns="http://www.w3.org/1999/xhtml">
+  <head>
+    <meta http-equiv="Content-Type" content="text/html; charset=utf-8" />
+    
+    <title>Overview — LLVM 3.9 documentation</title>
+    
+    <link rel="stylesheet" href="_static/llvm-theme.css" type="text/css" />
+    <link rel="stylesheet" href="_static/pygments.css" type="text/css" />
+    
+    <script type="text/javascript">
+      var DOCUMENTATION_OPTIONS = {
+        URL_ROOT:    './',
+        VERSION:     '3.9',
+        COLLAPSE_INDEX: false,
+        FILE_SUFFIX: '.html',
+        HAS_SOURCE:  true
+      };
+    </script>
+    <script type="text/javascript" src="_static/jquery.js"></script>
+    <script type="text/javascript" src="_static/underscore.js"></script>
+    <script type="text/javascript" src="_static/doctools.js"></script>
+    <link rel="top" title="LLVM 3.9 documentation" href="#" />
+    <link rel="next" title="LLVM Language Reference Manual" href="LangRef.html" />
+<style type="text/css">
+  table.right { float: right; margin-left: 20px; }
+  table.right td { border: 1px solid #ccc; }
+</style>
+
+  </head>
+  <body>
+<div class="logo">
+  <a href="#">
+    <img src="_static/logo.png"
+         alt="LLVM Logo" width="250" height="88"/></a>
+</div>
+
+    <div class="related">
+      <h3>Navigation</h3>
+      <ul>
+        <li class="right" style="margin-right: 10px">
+          <a href="genindex.html" title="General Index"
+             accesskey="I">index</a></li>
+        <li class="right" >
+          <a href="LangRef.html" title="LLVM Language Reference Manual"
+             accesskey="N">next</a> |</li>
+  <li><a href="http://llvm.org/">LLVM Home</a> | </li>
+  <li><a href="#">Documentation</a>»</li>
+ 
+      </ul>
+    </div>
+
+
+    <div class="document">
+      <div class="documentwrapper">
+          <div class="body">
+            
+  <div class="section" id="overview">
+<h1>Overview<a class="headerlink" href="#overview" title="Permalink to this headline">¶</a></h1>
+<p>The LLVM compiler infrastructure supports a wide range of projects, from
+industrial strength compilers to specialized JIT applications to small
+research projects.</p>
+<p>Similarly, documentation is broken down into several high-level groupings
+targeted at different audiences:</p>
+</div>
+<div class="section" id="llvm-design-overview">
+<h1>LLVM Design & Overview<a class="headerlink" href="#llvm-design-overview" title="Permalink to this headline">¶</a></h1>
+<p>Several introductory papers and presentations.</p>
+<div class="toctree-wrapper compound">
+</div>
+<dl class="docutils">
+<dt><a class="reference internal" href="LangRef.html"><em>LLVM Language Reference Manual</em></a></dt>
+<dd>Defines the LLVM intermediate representation.</dd>
+<dt><a class="reference external" href="http://llvm.org/pubs/2008-10-04-ACAT-LLVM-Intro.html">Introduction to the LLVM Compiler</a></dt>
+<dd>Presentation providing a users introduction to LLVM.</dd>
+<dt><a class="reference external" href="http://www.aosabook.org/en/llvm.html">Intro to LLVM</a></dt>
+<dd>Book chapter providing a compiler hacker’s introduction to LLVM.</dd>
+<dt><a class="reference external" href="http://llvm.org/pubs/2004-01-30-CGO-LLVM.html">LLVM: A Compilation Framework for Lifelong Program Analysis & Transformation</a></dt>
+<dd>Design overview.</dd>
+<dt><a class="reference external" href="http://llvm.org/pubs/2002-12-LattnerMSThesis.html">LLVM: An Infrastructure for Multi-Stage Optimization</a></dt>
+<dd>More details (quite old now).</dd>
+<dt><a class="reference external" href="http://llvm.org/pubs">Publications mentioning LLVM</a></dt>
+<dd></dd>
+</dl>
+</div>
+<div class="section" id="user-guides">
+<h1>User Guides<a class="headerlink" href="#user-guides" title="Permalink to this headline">¶</a></h1>
+<p>For those new to the LLVM system.</p>
+<p>NOTE: If you are a user who is only interested in using LLVM-based
+compilers, you should look into <a class="reference external" href="http://clang.llvm.org">Clang</a> or
+<a class="reference external" href="http://dragonegg.llvm.org">DragonEgg</a> instead. The documentation here is
+intended for users who have a need to work with the intermediate LLVM
+representation.</p>
+<div class="toctree-wrapper compound">
+</div>
+<dl class="docutils">
+<dt><a class="reference internal" href="GettingStarted.html"><em>Getting Started with the LLVM System</em></a></dt>
+<dd>Discusses how to get up and running quickly with the LLVM infrastructure.
+Everything from unpacking and compilation of the distribution to execution
+of some tools.</dd>
+<dt><a class="reference internal" href="CMake.html"><em>Building LLVM with CMake</em></a></dt>
+<dd>An addendum to the main Getting Started guide for those using the <a class="reference external" href="http://www.cmake.org">CMake
+build system</a>.</dd>
+<dt><a class="reference internal" href="HowToBuildOnARM.html"><em>How To Build On ARM</em></a></dt>
+<dd>Notes on building and testing LLVM/Clang on ARM.</dd>
+<dt><a class="reference internal" href="HowToCrossCompileLLVM.html"><em>How To Cross-Compile Clang/LLVM using Clang/LLVM</em></a></dt>
+<dd>Notes on cross-building and testing LLVM/Clang.</dd>
+<dt><a class="reference internal" href="GettingStartedVS.html"><em>Getting Started with the LLVM System using Microsoft Visual Studio</em></a></dt>
+<dd>An addendum to the main Getting Started guide for those using Visual Studio
+on Windows.</dd>
+<dt><a class="reference internal" href="tutorial/index.html"><em>LLVM Tutorial: Table of Contents</em></a></dt>
+<dd>Tutorials about using LLVM. Includes a tutorial about making a custom
+language with LLVM.</dd>
+<dt><a class="reference internal" href="CommandGuide/index.html"><em>LLVM Command Guide</em></a></dt>
+<dd>A reference manual for the LLVM command line utilities (“man” pages for LLVM
+tools).</dd>
+<dt><a class="reference internal" href="Passes.html"><em>LLVM’s Analysis and Transform Passes</em></a></dt>
+<dd>A list of optimizations and analyses implemented in LLVM.</dd>
+<dt><a class="reference internal" href="FAQ.html"><em>Frequently Asked Questions (FAQ)</em></a></dt>
+<dd>A list of common questions and problems and their solutions.</dd>
+<dt><a class="reference internal" href="ReleaseNotes.html"><em>Release notes for the current release</em></a></dt>
+<dd>This describes new features, known bugs, and other limitations.</dd>
+<dt><a class="reference internal" href="HowToSubmitABug.html"><em>How to submit an LLVM bug report</em></a></dt>
+<dd>Instructions for properly submitting information about any bugs you run into
+in the LLVM system.</dd>
+<dt><a class="reference internal" href="SphinxQuickstartTemplate.html"><em>Sphinx Quickstart Template</em></a></dt>
+<dd>A template + tutorial for writing new Sphinx documentation. It is meant
+to be read in source form.</dd>
+<dt><a class="reference internal" href="TestingGuide.html"><em>LLVM Testing Infrastructure Guide</em></a></dt>
+<dd>A reference manual for using the LLVM testing infrastructure.</dd>
+<dt><a class="reference external" href="http://clang.llvm.org/get_started.html">How to build the C, C++, ObjC, and ObjC++ front end</a></dt>
+<dd>Instructions for building the clang front-end from source.</dd>
+<dt><a class="reference internal" href="Lexicon.html"><em>The LLVM Lexicon</em></a></dt>
+<dd>Definition of acronyms, terms and concepts used in LLVM.</dd>
+<dt><a class="reference internal" href="HowToAddABuilder.html"><em>How To Add Your Build Configuration To LLVM Buildbot Infrastructure</em></a></dt>
+<dd>Instructions for adding new builder to LLVM buildbot master.</dd>
+<dt><a class="reference internal" href="YamlIO.html"><em>YAML I/O</em></a></dt>
+<dd>A reference guide for using LLVM’s YAML I/O library.</dd>
+<dt><a class="reference internal" href="GetElementPtr.html"><em>The Often Misunderstood GEP Instruction</em></a></dt>
+<dd>Answers to some very frequent questions about LLVM’s most frequently
+misunderstood instruction.</dd>
+<dt><a class="reference internal" href="Frontend/PerformanceTips.html"><em>Performance Tips for Frontend Authors</em></a></dt>
+<dd>A collection of tips for frontend authors on how to generate IR
+which LLVM is able to effectively optimize.</dd>
+</dl>
+</div>
+<div class="section" id="programming-documentation">
+<h1>Programming Documentation<a class="headerlink" href="#programming-documentation" title="Permalink to this headline">¶</a></h1>
+<p>For developers of applications which use LLVM as a library.</p>
+<div class="toctree-wrapper compound">
+</div>
+<dl class="docutils">
+<dt><a class="reference internal" href="LangRef.html"><em>LLVM Language Reference Manual</em></a></dt>
+<dd>Defines the LLVM intermediate representation and the assembly form of the
+different nodes.</dd>
+<dt><a class="reference internal" href="Atomics.html"><em>LLVM Atomic Instructions and Concurrency Guide</em></a></dt>
+<dd>Information about LLVM’s concurrency model.</dd>
+<dt><a class="reference internal" href="ProgrammersManual.html"><em>LLVM Programmer’s Manual</em></a></dt>
+<dd>Introduction to the general layout of the LLVM sourcebase, important classes
+and APIs, and some tips & tricks.</dd>
+<dt><a class="reference internal" href="Extensions.html"><em>LLVM Extensions</em></a></dt>
+<dd>LLVM-specific extensions to tools and formats LLVM seeks compatibility with.</dd>
+<dt><a class="reference internal" href="CommandLine.html"><em>CommandLine 2.0 Library Manual</em></a></dt>
+<dd>Provides information on using the command line parsing library.</dd>
+<dt><a class="reference internal" href="CodingStandards.html"><em>LLVM Coding Standards</em></a></dt>
+<dd>Details the LLVM coding standards and provides useful information on writing
+efficient C++ code.</dd>
+<dt><a class="reference internal" href="HowToSetUpLLVMStyleRTTI.html"><em>How to set up LLVM-style RTTI for your class hierarchy</em></a></dt>
+<dd>How to make <tt class="docutils literal"><span class="pre">isa<></span></tt>, <tt class="docutils literal"><span class="pre">dyn_cast<></span></tt>, etc. available for clients of your
+class hierarchy.</dd>
+<dt><a class="reference internal" href="ExtendingLLVM.html"><em>Extending LLVM: Adding instructions, intrinsics, types, etc.</em></a></dt>
+<dd>Look here to see how to add instructions and intrinsics to LLVM.</dd>
+<dt><a class="reference external" href="http://llvm.org/doxygen/">Doxygen generated documentation</a></dt>
+<dd>(<a class="reference external" href="http://llvm.org/doxygen/inherits.html">classes</a>)
+(<a class="reference external" href="http://llvm.org/doxygen/doxygen.tar.gz">tarball</a>)</dd>
+</dl>
+<p><a class="reference external" href="http://godoc.org/llvm.org/llvm/bindings/go/llvm">Documentation for Go bindings</a></p>
+<dl class="docutils">
+<dt><a class="reference external" href="http://llvm.org/viewvc/">ViewVC Repository Browser</a></dt>
+<dd></dd>
+<dt><a class="reference internal" href="CompilerWriterInfo.html"><em>Architecture & Platform Information for Compiler Writers</em></a></dt>
+<dd>A list of helpful links for compiler writers.</dd>
+<dt><a class="reference internal" href="LibFuzzer.html"><em>libFuzzer – a library for coverage-guided fuzz testing.</em></a></dt>
+<dd>A library for writing in-process guided fuzzers.</dd>
+<dt><a class="reference internal" href="ScudoHardenedAllocator.html"><em>Scudo Hardened Allocator</em></a></dt>
+<dd>A library that implements a security-hardened <cite>malloc()</cite>.</dd>
+</dl>
+</div>
+<div class="section" id="subsystem-documentation">
+<h1>Subsystem Documentation<a class="headerlink" href="#subsystem-documentation" title="Permalink to this headline">¶</a></h1>
+<p>For API clients and LLVM developers.</p>
+<div class="toctree-wrapper compound">
+</div>
+<dl class="docutils">
+<dt><a class="reference internal" href="WritingAnLLVMPass.html"><em>Writing an LLVM Pass</em></a></dt>
+<dd>Information on how to write LLVM transformations and analyses.</dd>
+<dt><a class="reference internal" href="WritingAnLLVMBackend.html"><em>Writing an LLVM Backend</em></a></dt>
+<dd>Information on how to write LLVM backends for machine targets.</dd>
+<dt><a class="reference internal" href="CodeGenerator.html"><em>The LLVM Target-Independent Code Generator</em></a></dt>
+<dd>The design and implementation of the LLVM code generator.  Useful if you are
+working on retargetting LLVM to a new architecture, designing a new codegen
+pass, or enhancing existing components.</dd>
+<dt><a class="reference internal" href="MIRLangRef.html"><em>Machine IR (MIR) Format Reference Manual</em></a></dt>
+<dd>A reference manual for the MIR serialization format, which is used to test
+LLVM’s code generation passes.</dd>
+<dt><a class="reference internal" href="TableGen/index.html"><em>TableGen</em></a></dt>
+<dd>Describes the TableGen tool, which is used heavily by the LLVM code
+generator.</dd>
+<dt><a class="reference internal" href="AliasAnalysis.html"><em>LLVM Alias Analysis Infrastructure</em></a></dt>
+<dd>Information on how to write a new alias analysis implementation or how to
+use existing analyses.</dd>
+<dt><a class="reference internal" href="GarbageCollection.html"><em>Garbage Collection with LLVM</em></a></dt>
+<dd>The interfaces source-language compilers should use for compiling GC’d
+programs.</dd>
+<dt><a class="reference internal" href="SourceLevelDebugging.html"><em>Source Level Debugging with LLVM</em></a></dt>
+<dd>This document describes the design and philosophy behind the LLVM
+source-level debugger.</dd>
+<dt><a class="reference internal" href="Vectorizers.html"><em>Auto-Vectorization in LLVM</em></a></dt>
+<dd>This document describes the current status of vectorization in LLVM.</dd>
+<dt><a class="reference internal" href="ExceptionHandling.html"><em>Exception Handling in LLVM</em></a></dt>
+<dd>This document describes the design and implementation of exception handling
+in LLVM.</dd>
+<dt><a class="reference internal" href="Bugpoint.html"><em>LLVM bugpoint tool: design and usage</em></a></dt>
+<dd>Automatic bug finder and test-case reducer description and usage
+information.</dd>
+<dt><a class="reference internal" href="BitCodeFormat.html"><em>LLVM Bitcode File Format</em></a></dt>
+<dd>This describes the file format and encoding used for LLVM “bc” files.</dd>
+<dt><a class="reference internal" href="SystemLibrary.html"><em>System Library</em></a></dt>
+<dd>This document describes the LLVM System Library (<tt class="docutils literal"><span class="pre">lib/System</span></tt>) and
+how to keep LLVM source code portable</dd>
+<dt><a class="reference internal" href="LinkTimeOptimization.html"><em>LLVM Link Time Optimization: Design and Implementation</em></a></dt>
+<dd>This document describes the interface between LLVM intermodular optimizer
+and the linker and its design</dd>
+<dt><a class="reference internal" href="GoldPlugin.html"><em>The LLVM gold plugin</em></a></dt>
+<dd>How to build your programs with link-time optimization on Linux.</dd>
+<dt><a class="reference internal" href="DebuggingJITedCode.html"><em>Debugging JIT-ed Code With GDB</em></a></dt>
+<dd>How to debug JITed code with GDB.</dd>
+<dt><a class="reference internal" href="MCJITDesignAndImplementation.html"><em>MCJIT Design and Implementation</em></a></dt>
+<dd>Describes the inner workings of MCJIT execution engine.</dd>
+<dt><a class="reference internal" href="BranchWeightMetadata.html"><em>LLVM Branch Weight Metadata</em></a></dt>
+<dd>Provides information about Branch Prediction Information.</dd>
+<dt><a class="reference internal" href="BlockFrequencyTerminology.html"><em>LLVM Block Frequency Terminology</em></a></dt>
+<dd>Provides information about terminology used in the <tt class="docutils literal"><span class="pre">BlockFrequencyInfo</span></tt>
+analysis pass.</dd>
+<dt><a class="reference internal" href="SegmentedStacks.html"><em>Segmented Stacks in LLVM</em></a></dt>
+<dd>This document describes segmented stacks and how they are used in LLVM.</dd>
+<dt><a class="reference internal" href="MarkedUpDisassembly.html"><em>LLVM’s Optional Rich Disassembly Output</em></a></dt>
+<dd>This document describes the optional rich disassembly output syntax.</dd>
+<dt><a class="reference internal" href="HowToUseAttributes.html"><em>How To Use Attributes</em></a></dt>
+<dd>Answers some questions about the new Attributes infrastructure.</dd>
+<dt><a class="reference internal" href="NVPTXUsage.html"><em>User Guide for NVPTX Back-end</em></a></dt>
+<dd>This document describes using the NVPTX back-end to compile GPU kernels.</dd>
+<dt><a class="reference internal" href="AMDGPUUsage.html"><em>User Guide for AMDGPU Back-end</em></a></dt>
+<dd>This document describes how to use the AMDGPU back-end.</dd>
+<dt><a class="reference internal" href="StackMaps.html"><em>Stack maps and patch points in LLVM</em></a></dt>
+<dd>LLVM support for mapping instruction addresses to the location of
+values and allowing code to be patched.</dd>
+<dt><a class="reference internal" href="BigEndianNEON.html"><em>Using ARM NEON instructions in big endian mode</em></a></dt>
+<dd>LLVM’s support for generating NEON instructions on big endian ARM targets is
+somewhat nonintuitive. This document explains the implementation and rationale.</dd>
+<dt><a class="reference internal" href="CoverageMappingFormat.html"><em>LLVM Code Coverage Mapping Format</em></a></dt>
+<dd>This describes the format and encoding used for LLVM’s code coverage mapping.</dd>
+<dt><a class="reference internal" href="Statepoints.html"><em>Garbage Collection Safepoints in LLVM</em></a></dt>
+<dd>This describes a set of experimental extensions for garbage
+collection support.</dd>
+<dt><a class="reference internal" href="MergeFunctions.html"><em>MergeFunctions pass, how it works</em></a></dt>
+<dd>Describes functions merging optimization.</dd>
+<dt><a class="reference internal" href="InAlloca.html"><em>Design and Usage of the InAlloca Attribute</em></a></dt>
+<dd>Description of the <tt class="docutils literal"><span class="pre">inalloca</span></tt> argument attribute.</dd>
+<dt><a class="reference internal" href="FaultMaps.html"><em>FaultMaps and implicit checks</em></a></dt>
+<dd>LLVM support for folding control flow into faulting machine instructions.</dd>
+<dt><a class="reference internal" href="CompileCudaWithLLVM.html"><em>Compiling CUDA C/C++ with LLVM</em></a></dt>
+<dd>LLVM support for CUDA.</dd>
+</dl>
+</div>
+<div class="section" id="development-process-documentation">
+<h1>Development Process Documentation<a class="headerlink" href="#development-process-documentation" title="Permalink to this headline">¶</a></h1>
+<p>Information about LLVM’s development process.</p>
+<div class="toctree-wrapper compound">
+</div>
+<dl class="docutils">
+<dt><a class="reference internal" href="DeveloperPolicy.html"><em>LLVM Developer Policy</em></a></dt>
+<dd>The LLVM project’s policy towards developers and their contributions.</dd>
+<dt><a class="reference internal" href="Projects.html"><em>Creating an LLVM Project</em></a></dt>
+<dd>How-to guide and templates for new projects that <em>use</em> the LLVM
+infrastructure.  The templates (directory organization, Makefiles, and test
+tree) allow the project code to be located outside (or inside) the <tt class="docutils literal"><span class="pre">llvm/</span></tt>
+tree, while using LLVM header files and libraries.</dd>
+<dt><a class="reference internal" href="LLVMBuild.html"><em>LLVMBuild Guide</em></a></dt>
+<dd>Describes the LLVMBuild organization and files used by LLVM to specify
+component descriptions.</dd>
+<dt><a class="reference internal" href="HowToReleaseLLVM.html"><em>How To Release LLVM To The Public</em></a></dt>
+<dd>This is a guide to preparing LLVM releases. Most developers can ignore it.</dd>
+<dt><a class="reference internal" href="ReleaseProcess.html"><em>How To Validate a New Release</em></a></dt>
+<dd>This is a guide to validate a new release, during the release process. Most developers can ignore it.</dd>
+<dt><a class="reference internal" href="Packaging.html"><em>Advice on Packaging LLVM</em></a></dt>
+<dd>Advice on packaging LLVM into a distribution.</dd>
+<dt><a class="reference internal" href="Phabricator.html"><em>Code Reviews with Phabricator</em></a></dt>
+<dd>Describes how to use the Phabricator code review tool hosted on
+<a class="reference external" href="http://reviews.llvm.org/">http://reviews.llvm.org/</a> and its command line interface, Arcanist.</dd>
+</dl>
+</div>
+<div class="section" id="community">
+<h1>Community<a class="headerlink" href="#community" title="Permalink to this headline">¶</a></h1>
+<p>LLVM has a thriving community of friendly and helpful developers.
+The two primary communication mechanisms in the LLVM community are mailing
+lists and IRC.</p>
+<div class="section" id="mailing-lists">
+<h2>Mailing Lists<a class="headerlink" href="#mailing-lists" title="Permalink to this headline">¶</a></h2>
+<p>If you can’t find what you need in these docs, try consulting the mailing
+lists.</p>
+<dl class="docutils">
+<dt><a class="reference external" href="http://lists.llvm.org/mailman/listinfo/llvm-dev">Developer’s List (llvm-dev)</a></dt>
+<dd>This list is for people who want to be included in technical discussions of
+LLVM. People post to this list when they have questions about writing code
+for or using the LLVM tools. It is relatively low volume.</dd>
+<dt><a class="reference external" href="http://lists.llvm.org/pipermail/llvm-commits/">Commits Archive (llvm-commits)</a></dt>
+<dd>This list contains all commit messages that are made when LLVM developers
+commit code changes to the repository. It also serves as a forum for
+patch review (i.e. send patches here). It is useful for those who want to
+stay on the bleeding edge of LLVM development. This list is very high
+volume.</dd>
+<dt><a class="reference external" href="http://lists.llvm.org/pipermail/llvm-bugs/">Bugs & Patches Archive (llvm-bugs)</a></dt>
+<dd>This list gets emailed every time a bug is opened and closed. It is
+higher volume than the LLVM-dev list.</dd>
+<dt><a class="reference external" href="http://lists.llvm.org/pipermail/llvm-testresults/">Test Results Archive (llvm-testresults)</a></dt>
+<dd>A message is automatically sent to this list by every active nightly tester
+when it completes.  As such, this list gets email several times each day,
+making it a high volume list.</dd>
+<dt><a class="reference external" href="http://lists.llvm.org/mailman/listinfo/llvm-announce">LLVM Announcements List (llvm-announce)</a></dt>
+<dd>This is a low volume list that provides important announcements regarding
+LLVM.  It gets email about once a month.</dd>
+</dl>
+</div>
+<div class="section" id="irc">
+<h2>IRC<a class="headerlink" href="#irc" title="Permalink to this headline">¶</a></h2>
+<p>Users and developers of the LLVM project (including subprojects such as Clang)
+can be found in #llvm on <a class="reference external" href="irc://irc.oftc.net/llvm">irc.oftc.net</a>.</p>
+<p>This channel has several bots.</p>
+<ul class="simple">
+<li>Buildbot reporters<ul>
+<li>llvmbb - Bot for the main LLVM buildbot master.
+<a class="reference external" href="http://lab.llvm.org:8011/console">http://lab.llvm.org:8011/console</a></li>
+<li>bb-chapuni - An individually run buildbot master. <a class="reference external" href="http://bb.pgr.jp/console">http://bb.pgr.jp/console</a></li>
+<li>smooshlab - Apple’s internal buildbot master.</li>
+</ul>
+</li>
+<li>robot - Bugzilla linker. %bug <number></li>
+<li>clang-bot - A <a class="reference external" href="http://www.eelis.net/geordi/">geordi</a> instance running
+near-trunk clang instead of gcc.</li>
+</ul>
+</div>
+</div>
+<div class="section" id="indices-and-tables">
+<h1>Indices and tables<a class="headerlink" href="#indices-and-tables" title="Permalink to this headline">¶</a></h1>
+<ul class="simple">
+<li><a class="reference internal" href="genindex.html"><em>Index</em></a></li>
+<li><a class="reference internal" href="search.html"><em>Search Page</em></a></li>
+</ul>
+</div>
+
+
+          </div>
+      </div>
+      <div class="clearer"></div>
+    </div>
+    <div class="related">
+      <h3>Navigation</h3>
+      <ul>
+        <li class="right" style="margin-right: 10px">
+          <a href="genindex.html" title="General Index"
+             >index</a></li>
+        <li class="right" >
+          <a href="LangRef.html" title="LLVM Language Reference Manual"
+             >next</a> |</li>
+  <li><a href="http://llvm.org/">LLVM Home</a> | </li>
+  <li><a href="#">Documentation</a>»</li>
+ 
+      </ul>
+    </div>
+    <div class="footer">
+        © Copyright 2003-2016, LLVM Project.
+      Last updated on 2016-12-21.
+      Created using <a href="http://sphinx-doc.org/">Sphinx</a> 1.2.2.
+    </div>
+  </body>
+</html>
\ No newline at end of file

Added: www-releases/trunk/3.9.1/docs/objects.inv
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/objects.inv?rev=290368&view=auto
==============================================================================
Binary file - no diff available.

Propchange: www-releases/trunk/3.9.1/docs/objects.inv
------------------------------------------------------------------------------
    svn:mime-type = application/octet-stream

Added: www-releases/trunk/3.9.1/docs/search.html
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/search.html?rev=290368&view=auto
==============================================================================
--- www-releases/trunk/3.9.1/docs/search.html (added)
+++ www-releases/trunk/3.9.1/docs/search.html Thu Dec 22 14:04:03 2016
@@ -0,0 +1,111 @@
+
+<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN"
+  "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd">
+
+
+<html xmlns="http://www.w3.org/1999/xhtml">
+  <head>
+    <meta http-equiv="Content-Type" content="text/html; charset=utf-8" />
+    
+    <title>Search — LLVM 3.9 documentation</title>
+    
+    <link rel="stylesheet" href="_static/llvm-theme.css" type="text/css" />
+    <link rel="stylesheet" href="_static/pygments.css" type="text/css" />
+    
+    <script type="text/javascript">
+      var DOCUMENTATION_OPTIONS = {
+        URL_ROOT:    './',
+        VERSION:     '3.9',
+        COLLAPSE_INDEX: false,
+        FILE_SUFFIX: '.html',
+        HAS_SOURCE:  true
+      };
+    </script>
+    <script type="text/javascript" src="_static/jquery.js"></script>
+    <script type="text/javascript" src="_static/underscore.js"></script>
+    <script type="text/javascript" src="_static/doctools.js"></script>
+    <script type="text/javascript" src="_static/searchtools.js"></script>
+    <link rel="top" title="LLVM 3.9 documentation" href="index.html" />
+  <script type="text/javascript">
+    jQuery(function() { Search.loadIndex("searchindex.js"); });
+  </script>
+  
+  <script type="text/javascript" id="searchindexloader"></script>
+  
+<style type="text/css">
+  table.right { float: right; margin-left: 20px; }
+  table.right td { border: 1px solid #ccc; }
+</style>
+
+
+  </head>
+  <body>
+<div class="logo">
+  <a href="index.html">
+    <img src="_static/logo.png"
+         alt="LLVM Logo" width="250" height="88"/></a>
+</div>
+
+    <div class="related">
+      <h3>Navigation</h3>
+      <ul>
+        <li class="right" style="margin-right: 10px">
+          <a href="genindex.html" title="General Index"
+             accesskey="I">index</a></li>
+  <li><a href="http://llvm.org/">LLVM Home</a> | </li>
+  <li><a href="index.html">Documentation</a>»</li>
+ 
+      </ul>
+    </div>
+
+
+    <div class="document">
+      <div class="documentwrapper">
+          <div class="body">
+            
+  <h1 id="search-documentation">Search</h1>
+  <div id="fallback" class="admonition warning">
+  <script type="text/javascript">$('#fallback').hide();</script>
+  <p>
+    Please activate JavaScript to enable the search
+    functionality.
+  </p>
+  </div>
+  <p>
+    From here you can search these documents. Enter your search
+    words into the box below and click "search". Note that the search
+    function will automatically search for all of the words. Pages
+    containing fewer words won't appear in the result list.
+  </p>
+  <form action="" method="get">
+    <input type="text" name="q" value="" />
+    <input type="submit" value="search" />
+    <span id="search-progress" style="padding-left: 10px"></span>
+  </form>
+  
+  <div id="search-results">
+  
+  </div>
+
+          </div>
+      </div>
+      <div class="clearer"></div>
+    </div>
+    <div class="related">
+      <h3>Navigation</h3>
+      <ul>
+        <li class="right" style="margin-right: 10px">
+          <a href="genindex.html" title="General Index"
+             >index</a></li>
+  <li><a href="http://llvm.org/">LLVM Home</a> | </li>
+  <li><a href="index.html">Documentation</a>»</li>
+ 
+      </ul>
+    </div>
+    <div class="footer">
+        © Copyright 2003-2016, LLVM Project.
+      Last updated on 2016-12-21.
+      Created using <a href="http://sphinx-doc.org/">Sphinx</a> 1.2.2.
+    </div>
+  </body>
+</html>
\ No newline at end of file

Added: www-releases/trunk/3.9.1/docs/searchindex.js
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/searchindex.js?rev=290368&view=auto
==============================================================================
--- www-releases/trunk/3.9.1/docs/searchindex.js (added)
+++ www-releases/trunk/3.9.1/docs/searchindex.js Thu Dec 22 14:04:03 2016
@@ -0,0 +1 @@
+Search.setIndex({envversion:42,terms:{func:[80,10,36,86,16,17,18,19,20,22,23],orthogon:53,interchang:[94,101],four:[29,124,66,11,82,28,2,30,58,53,101,88,114,94,36,9,23],prefix:[],grokabl:101,is_open:11,francesco:48,atomicrmw:[],add32ri8:8,uint64_max:70,identityprop:20,foldingsetnodeid:20,lore:125,build_fcmp:[16,17,18,19,23],dbx:115,digit:[36,28,37,20],intregsregclass:66,emitconst:66,basic_:128,n2118:101,delv:[16,43,30],f110:11,codlay:59,configstatusscript:[],bdist_egg:51,amdhsa:94,distcheckdir:[],fpmad:115,mli:16,seper:[],second:[48,101,1,50,51,26,104,54,78,4,7,9,80,107,36,115,15,81,17,20,23,24,25,2,66,114,82,28,29,30,31,32,33,86,38,119,40,120,42,94,95,96,76,97,124,127],x86ii:66,r15d:8,functionfaultinfo:100,r15b:8,alignstack:[36,124],thefpm:[30,31,32,33],constrast:58,r15w:8,xchg:[36,53],cull:101,ongo:[40,43,0],noreturn:[36,63,124],visitxor:93,here:[101,0,120,76,50,51,26,52,104,96,125,78,4,5,6,7,8,9,80,56,94,11,113,59,115,108,62,13,15,63,81,16,17,18,19,20,111,22,23,24,25,109,66,114,8
 2,27,28,29,30,31,32,33,86,36,107,38,72,119,39,85,93,42,58,95,53,121,99,97,83,126,40,128,46,47,110],gnu_hash:115,fuzzing_build_mode_unsafe_for_product:42,image_file_machine_r4000:121,dllvm_build_runtim:38,iseldagtodag:34,setschedulingprefer:[],sorri:[26,15],golden:101,argn:81,unic:28,bou_tru:28,unif:58,protoast:[24,25,29,30,31,32,33],brought:50,substr:80,unix:[38,72,107,20,28,108,13,36,4,7],machinecodeemitt:66,content_disposition_typ:43,globalvari:[],unit:[],ldri:66,fstream:11,subpath:[44,2],destarglist:36,get_ptr:100,inner:[56,41,101,36,76,61,120,81,20],until:[48,101,0,49,2,111,59,62,9,85,36,13,63,16,17,18,19,20,21,22,23,24,25,66,27,28,29,30,31,32,33,86,34,88,68,37,38,41,119,39,93,42,94,43,124,120],new_else_bb:[17,18,19],emitlabelplusoffset:82,v8p0f_i32f:36,jmp:36,relat:[],notic:[94,72,113,11,50,29,33,43,63,81,114,19,20,108,23],hurt:101,initialize_pass_depend:86,exce:[101,36,115],"_dcleanup":120,hole:[28,36],herebi:101,image_scn_align_128byt:121,catch3:120,generalis:[18,32],talli:51
 ,dagtodag:57,conceptu:[101,114,7,28,94,120,88,36,20],forexpr:[24,25,31,32,33,17,18,19],oftc:56,rework:[28,43],get_matcher_implement:34,al_superregsset:66,phabric:[],dtor:[108,36],createfunct:25,replaceusesofwith:[71,20],doubletyp:20,caution:[40,53],fibonacci:[27,96,21],want:[],umin:36,"__sync_fetch_and_and_n":53,hasfp:66,canfail:20,mcasmstream:94,fucompi:94,hoc:[48,94,20],mov32mr:83,classifi:58,i686:[13,94,7],how:[],hot:[40,36,63,70],actionscript:[26,15],symposium:14,macosx10:36,perspect:[0,102,113,58,40,86,120,36],lhse:[24,25,33],bpf_stx:94,decor:115,tls1_process_heartbeat:42,wrong:[],beauti:[27,29,32,18,21,23],adc32rm:8,outoperandlist:[8,66],weakanylinkag:20,index2virtreg:94,passopt:86,isvalid:25,apint:20,revolv:115,alias:[],"18th":114,prototypeast:[24,25,111,29,30,31,32,33,5,6],tok_for:[24,25,31,32,33],wind:20,"0b01101101":36,"0x3f":35,feedback:[0,104,86,43,126,5,6,59,62],readandmaybemodifi:42,"0x0abcd":36,appar:[19,33],vari:[38,94,102,36,42,26,53,93,15,124,4,20,108],exported_sym
 bol_list:[],redhat:74,fit:[48,101,119,114,36,28,94,14,31,54,43,88,17,20,62,115],fix:[],fib:[25,48,27,31,33,17,19,21],xxxinstrdescriptor:66,updatepoint:[5,6],hidden:[101,36,28,94,61,77,115,86,105,124,68,20,9],easier:[48,73,102,49,94,101,36,8,9,57,11,108,12,109,13,19,20,22,23,25,112,82,111,29,33,86,34,119,58,53,43,44],aliasesset:58,var1:81,proce:[71,72,49,50,82,120,20,62],imagstart:[18,32],interrupt:[100,101,42,2,4,36],sellect:34,kernelparam:11,loopinfo:86,sparclite86x:66,dcmake_install_prefix:[38,72,12,52],exprast:[24,25,111,29,30,31,32,33,5,6,22],accommod:[36,94,35,124,11],timeout:42,"0x7ffff7ed404c":109,build_fadd:23,openfileforwrit:4,resum:[],llvmfuzzertestoneinput:42,cprestor:47,pinsrd_1:7,numentri:124,whip:[18,32],intregssuperclass:66,dst:[78,94,8,66,128],dsp:47,astcontext:101,dso:53,dsl:[8,110],llvm_lit_arg:72,adapt:[4,108,20,48],dsa:71,committ:43,navig:[44,28,119],selectionkind:36,omiss:[43,36],targetloweringobjectfil:94,adc64ri32:8,md5:[80,43],f3_1:66,f3_2:66,f3_3:66,proj_src
 _root:64,reformul:58,realstart:[18,32],att:[90,87,36],unabl:[71,102,63,36,22,128],disablelazycompil:20,confus:[101,107,66,114,50,43,36,120,20],jitsymbolflag:[5,6,59,62,9],s3_pkt:42,catchswitch:[],configurescriptflag:[],clariti:[17,0,31,36],wast:[85,127,115,33,97,19,20],psubusw:13,mingw:[96,94,72,104],mklib:[],wasn:[24,25,58,50,32,33,18,19],isalnum:[24,25,27,111,29,30,31,32,33],llvmmemorymanagerallocatedatasectioncallback:97,signext:[36,124],setargstr:28,nobuiltin:36,master:[126,38,119,64,56],image_scn_mem_discard:121,similarli:[24,25,73,113,66,56,123,36,28,58,101,53,93,43,88,120,20,51],getnod:[57,66],image_sym_class_stat:121,linpack:1,"0b7654321":[],arrayidx1:36,arrayidx3:36,arrayidx2:36,arrayidx4:36,"0x3500000001652748":109,ntid:11,crawl:82,technic:[56,42,43,102,81],lvalu:20,tree:[],wchar_t:36,image_rel_i386_secrel:35,sdnode:[66,20,47,94,93,8],recheck:[48,50],uniniti:[101,114,82,42,36,128],runner:51,libllvmcor:20,reassur:42,aforement:38,"__atomic_store_n":53,increment:[],infring:43
 ,dcmake_toolchain_fil:38,incompat:[74,120,47,36],dozen:[52,63],sig_atomic_t:36,implicitus:94,musttail:[47,36],lfoo:94,eagerli:62,get_instrinfo_operand_types_enum:66,simplifi:[],shall:[72,28,26,15,36],cpu2:76,object:[],numloc:97,dblty:25,letter:[24,25,101,66,28,32,33,124,18,19,36],breakpoint:[],alwaysinlin:[36,124],errorv:[],getelementtyp:20,expr0rh:80,purgev:124,dummi:[48,108,66,94,13,128],lpm:86,mayreadfrommemori:53,detriment:101,came:[120,26,31,37,15,125,17],undefinit:36,superset:[36,53,107],asid:[36,54,20,42,39],sexist:102,advisori:102,addr2:89,klimek:119,matchinstructionimpl:94,layout:[],ccmake:72,apach:[4,43],llvmcore:[49,64],theme:[8,9,110],busi:43,image_sym_type_word:121,exctyp:120,recursivetarget:[],plate:28,selectiondagbuild:94,googlegroup:42,enable_profil:[],addri:66,replaceusesofwithonconst:71,addrr:66,ldm:36,smallvectorimpl:20,ppc_fp128:[50,36,124],tstri:83,ever:[101,58,59,26,43,15,36,44,20,9],patch:[],gpgpu:14,emitstorecondit:53,sligtli:88,bpf_ja:94,respond:[48,0,119,58
 ],sjljehprepar:120,mandatori:[36,96,20,63,66],fprofil:[80,105,72],fail:[],best:[],dw_tag_reference_typ:[36,115],wikipedia:[44,17,36,31],copyleft:43,figur:[86,101,66,36,28,73,93,13,88,94,20,62],irc:[],sysroot:[12,8],glasgow:36,fuzz_target:42,xvf:96,henrik:4,extend:[],extens:[],extent:[82,43,36,114,67],toler:[82,36,104],advertis:120,rtti:[],"_args_":81,"0f3f800000":11,llvmaddinstrattribut:47,accident:[86,4,28,101,20],atomicexpandpass:53,logic:[48,101,50,2,7,5,6,59,62,9,36,17,18,19,20,23,113,114,111,31,32,33,94,43,44],hh567368:101,compromis:20,with_assert:72,assur:76,mattr:[24,90,87,7,66],preemptibl:48,creategvnpass:[25,30,31,32,33,5,6,59,62],"2nd":[36,42,20,128],dibuild:[25,115],diff:[],summat:36,assum:[],summar:[82,48,2,94],duplic:[],frc:94,frb:94,fra:94,bewilder:[],union:[101,58,94,115,33,19,36],n_hash:115,frt:94,bpf_mod:94,life:[43,101,63],regul:86,p0v8p0f64:36,mrm6m:66,worker:42,earlyclobb:83,cufunct:11,lift:[62,63],legacypassmanag:[24,25,30,31,32,33],child:[120,18,36,113,32],obje
 ctfil:85,infocent:117,emploi:[36,20],"__sync_fetch_and_or_n":53,commerci:43,employ:43,one_onli:35,debug_metadata_vers:25,r_amdgpu_non:94,emit_22:66,unop:[24,25,32,33,18,19],"0xk":36,llvm_enable_p:72,filename0:80,lto_module_is_object_file_in_memori:99,libxml:42,leaksanit:42,createret:[24,25,29,30,31,32,33],format:[],bikesh:113,ebenders_test:109,generalcategori:28,falsedest:36,split:[48,57,66,114,50,28,94,95,53,93,43,88,83,36,64],immtypebit:8,functionpassmanag:[30,31,32,33,5,6,59,62,9],adl:111,annoat:45,reassoci:[],cxx0x:101,dest1:36,fairli:[66,58,27,42,108,31,32,53,15,63,111,44,17,18,20,21,22],dest2:36,boiler:28,ownership:[24,25,30,31,32,33,43,5,6,20],refin:[94,20,9,58],tune:[],instrprofvaluekind:36,tokvarnam:46,nuzman:1,gzip:38,argmemonli:[36,63],ordin:28,bit:[],previous:[72,66,51,36,28,30,31,62,105,47,120,104,46,42,23],fintegr:[],easi:[101,76,49,50,51,26,59,62,9,36,115,12,13,15,16,17,19,20,21,22,23,2,113,82,27,111,29,30,31,33,86,34,38,72,42,94,75,43,124,44,127],bitwidth:[50,36,124,
 40],had:[11,40,50,76,86,97,88,55,4,127,36,62,9],v4p0f_i32f:36,har:[38,64],hat:76,abort_on_timeout:42,sanit:[38,54,72,42,81],ocamlbuild:[16,17,18,19,22,23],sanir:42,preserv:[38,94,107,114,58,40,28,26,67,86,105,15,88,120,97,36,42],instrumen:80,llvmremoveinstrattribut:47,st_mode:107,attrparsedattrkind:34,isdeclar:20,measur:[42,107],specif:[],fcmpinst:20,nonlazybind:36,remind:[43,104],underli:[],right:[],old:[],getargumentlist:20,unabashedli:[],x86_fastcal:94,olt:36,paralleltarget:[],dominatorset:86,txt:[38,101,72,119,66,67,28,127,115,104,13,89,43,44,5,6,59,62,9],sparcsubtarget:66,bottom:[48,71,119,66,1,50,28,70,86,17,4,36,62,90],undisturb:101,lto_module_get_num_symbol:99,stringsort:101,subclass:[],cassert:[101,11,30,31,32,33],topleveltarget:[],op_begin:20,condit:[],foo:[101,1,40,3,122,7,80,11,36,108,61,13,81,16,17,94,20,111,22,23,113,114,82,28,29,30,31,115,35,88,89,70,72,120,42,73,58,76,123,46,128],"0f00000000":11,armv7a:104,sensibl:20,leftr:50,clientaddrlen:5,egregi:[43,102],tablegen:
 [],bindex:66,llvm_on_xyz:4,image_scn_mem_lock:121,llvmanalysi:64,true_branch_weight:3,troubl:[38,28,43,96],benderski:14,baselayert:62,slightli:[],xor64rr:94,dw_tag_array_typ:[36,115],llvmfuzzeriniti:42,selectiondagisel:[47,34],basenam:115,expandop:57,mbb:[47,94,66],creativ:[],mcinstlow:94,wrap:[101,4,36,9,85,61,63,81,20,111,22,23,114,27,28,29,115,38,76,21,43,124],msp430:[38,94,36],neatli:62,data32bitsdirect:66,suffici:[38,114,73,113,48,40,7,28,58,53,93,82,63,36,27,45,20,21,128],support:[],sub_rr:128,happi:[19,119,64,33],sub_ri:128,width:[],cpprefer:20,distsubdir:[],constantli:38,path_to_clang:125,use_back:20,headach:49,setxyzzi:101,"0x2413bc":86,fpga:94,offer:[82,47,76,20,53],unrool:14,refcount:82,strike:[29,23],dllstorageclass:[36,124],multiprocessor:[82,86],reserveresourc:94,profdata:[],mymod:[],"_main":[89,121],insidi:101,getdefaulttargettripl:24,reiter:36,handili:101,fermi:94,dump_valu:[16,17,18,19,23],rerun:[],isexternalsymbol:66,later:[48,101,50,51,105,7,9,80,36,115,13,63,81,1
 6,17,18,19,20,22,23,25,66,111,29,30,31,32,33,86,38,72,85,120,42,94,97,64,125,40,127,47],proven:[48,33,37,63,19,36],flagsflat:76,ericsson:36,build_phi:[17,18,19],bswap:[],relax:40,role:[101,49,50,111,115,46,22],finalizeobject:[85,25],presum:[36,119],smell:20,roll:[101,113],"_p1":115,legitim:101,notif:[119,58],intend:[],createargumentalloca:[25,33],removemoduleset:[5,6,59,62,9],substract:36,"__except":120,cudamalloc:14,intent:[107,36,94,33,43,99,88,81,19,46],keycol:78,"0b10110110":36,dyn_switch:101,"1s100000s11010s10100s1111s1010s110s11s1":20,padparam:120,cumemcpyhtod:11,isfloatingpointti:20,time:[],push:[25,101,82,47,94,93],image_file_dl:121,corpu:[],breadth:[27,21,90],mrmsrcmem:66,ptrtoint:[],oss:[],sparctargetmachin:66,osi:108,aptr:36,const_nul:[17,18,19],inaddr_ani:5,image_sym_type_short:121,decid:[57,76,72,119,1,36,28,73,115,32,33,86,120,88,40,16,18,19,20,111,22],hold:[48,102,50,54,5,6,59,8,9,85,36,115,62,13,16,17,18,19,20,111,22,23,24,25,66,82,27,28,29,30,31,32,33,86,38,120,42,9
 4,64,125,44,128],decim:[107,28,76,122,37,35,36,128],strequal:81,x08:121,decis:[101,0,102,1,40,94,30,43,63,88,120,16,93,62],x03:121,x01:121,macho:[85,94,124],x04:121,cheap:[59,101,20,53],"__atomic_fetch_or_n":53,uint32_max:115,cudevicecomputecap:11,vmcore:28,lrt:14,fullest:101,exact:[38,101,120,48,82,36,28,67,53,115,86,99,83,44,20,51],numlin:80,solver:94,tear:120,identifierstr:[24,25,27,111,29,30,31,32,33],unsupport:[94,66,49,2,53,104,13,96],team:[64,104],cooki:[36,20],prevent:[48,101,1,40,54,4,5,6,7,9,58,36,108,13,14,81,19,20,23,24,25,82,28,29,115,33,86,47,94,95,43,97],dcmake_cxx_flag:12,numroot:82,heavyweight:20,relocat:[85,90,94,36,66],llvm_lit_tools_dir:[96,72],regex_t:42,filenameindex1:80,lazili:[20,99,124,16,5,6,59,62,9],currenc:[16,94,43,30],thecu:25,merge_bb:[17,18,19],current:[0,2,3,4,7,8,9,11,12,13,15,16,17,18,19,20,21,22,23,24,25,26,27,111,29,30,31,32,33,34,35,38,39,40,42,43,44,46,47,48,96,49,50,54,56,57,58,41,61,62,63,64,85,66,37,72,76,74,75,78,36,80,81,82,83,86,87,88,90,
 94,95,53,97,100,101,102,104,107,108,28,114,115,119,120,123,124,126,128],image_scn_cnt_cod:121,i256:36,objdir:[],addpdrr:128,handleterminatesess:5,intraprocedur:93,unvectoriz:1,cudevicegetnam:11,dropdown:119,autogener:43,live_begin:82,splice:[36,20],address:[],along:[],ffast:[14,1],cur_var:19,volumin:20,checksum:[54,42],commentstr:66,errorhandl:[],queue:[86,20,66],throughput:63,replaceinstwithvalu:20,safepoint:[],mipsel:47,bpf_ld:94,commonli:[101,66,82,20,124,36],ourselv:[101,115,9,11],ipc:4,ipa:71,love:20,"2ap3":35,pentium:[38,66],prefer:[],ipo:[50,71],src2:[94,8,128],regalloc:[86,90,87,94],src1:[94,8,128],fake:90,instal:[],llvm_lib_search_path:[],anothercategori:28,virtreg:94,image_sym_class_nul:121,abbrevid:124,scope:[],tightli:[24,25,101,111,29,30,31,32,33,16,17,18,19,36,22,23],analyz:[],"66ghz":126,peopl:[38,57,101,102,119,56,49,27,28,26,86,43,15,47,4,114,94,36,21,9,108],n2627:101,claus:[94,43,36,120],refrain:[36,0,104],enhanc:[],dagarg:46,linkmodul:[],langref:[57,63,53],easiest
 :[38,66,26,30,53,104,86,15,127],behalf:[43,119],b_ctor_bas:7,subel:36,my_fuzz:42,descriptor:[25,66,115,97,124,36],valuet:20,whatev:[38,76,72,114,48,36,28,58,12,120,4,7,9],problemat:101,encapsul:[101,113,68],myremot:5,recycl:94,setrecordnam:124,optnon:36,fpm:[5,6,59,62],r11b:8,r11d:8,forexprast:[24,25,31,32,33],fpu:[36,47,12],rel_path_to_fil:105,parameter:128,r11w:8,vec0123:36,remap:[],jazz:64,dw_apple_property_gett:115,spot:[48,42,104],mrm4m:66,mrm4r:66,succ:101,date:[38,107,119,58,49,47,12,31,104,96,17,93,128],shuffl:[2,36],data:[],codes:8,stress:[],rc2:49,indexloc:20,bpf_xor:94,disable_auto_depend:[],stdio:[38,75,96,17,16,4,18,19,99],stdin:[25,115,13,105,16,17,18,19,7,22,23],fp5:[8,128],fp4:[8,128],sandbox:[49,12],fp6:[8,128],fp1:[8,128],fp0:[8,128],fp3:[8,128],fp2:[8,128],callabl:[],iftmp:[24,25,31,32,33,17,18,19],untest:49,denot:[38,76,82,94,124,36],use_llvm_executionengin:[16,17,18,19],my_funct:11,llvm_library_vis:82,revisit:40,numbyt:97,x86retflag:128,overhaul:104,thumb:[],ima
 ge_sym_class_block:121,precedecnc:[24,25,32,33],instantli:20,"__stack_chk_guard":36,jit:[],canonicalis:88,image_sym_class_end_of_struct:121,mips32r2:[],alacconvert:51,outli:120,mips32r5:[],mips32r6:47,smarter:28,isbinaryop:[24,25,32,33],nation:102,"0x00000147":115,inpredsens:78,therebi:[97,28,36],"0x00000140":115,maxatomicsizeinbitssupport:53,machineconstantpoolvalu:83,mcode:35,revers:[],llvm_src_dir:52,separ:[101,0,76,51,2,105,4,5,7,11,36,12,61,13,81,20,111,64,66,114,82,28,30,115,86,34,37,70,38,72,42,94,53,122,43,97,22,124,44,127,99,128],xctoolchain:72,dwarf2:25,complextyp:121,sk_squar:113,compil:[],argvalu:[28,109],insertbyt:42,receipt:0,"0x4000":115,registertarget:66,"__has_attribut":34,blx:35,movsx64rr32:94,"0x100":115,blk:20,nsw:[43,36,63,114],getschedclass:66,pseudocod:66,million:[36,20],removefrompar:20,crazier:[17,31],"byte":[40,54,55,36,80,57,107,58,16,17,18,19,20,22,23,66,114,115,88,42,94,95,53,123,97,124],reusabl:94,departur:[],jitcompilerfunct:66,setdefault:[],ifuzz:42,s
 ysconfdir:[],modest:101,recov:[100,7,42,97,36,120,20],cbw:94,nicknam:0,neglect:51,arraytyp:20,trytohandl:20,oper:[],onc:[100,101,0,120,76,49,50,51,26,104,105,54,84,4,5,6,59,8,85,56,10,94,58,36,108,62,15,81,16,17,19,20,111,22,23,2,66,114,82,99,28,29,30,31,33,86,38,41,71,72,119,40,93,42,73,96,122,75,43,124,57,127,46,128],iaddroff:94,coveragemappingdataforfunctionrecord1:80,"0x7f":[36,128],printinformationalmessag:28,symmetri:13,spanish:54,open:[],lexicograph:[50,101],addtmp4:[29,23],insttoreplac:20,f88:11,convent:[],bite:108,broadcom:47,f80:36,enable_optim:[74,104],optlevel:28,draft:[38,115,0,53,102],addtmp1:[16,30],getsubtarget:66,conveni:[48,101,26,36,9,80,11,13,15,17,18,20,64,2,113,28,30,31,32,94,43,128],goldberg91:82,usenamedoperandt:66,fma:[],eor:36,sometest:51,programat:[18,94,32],insertion_block:[17,18,19],artifact:[50,42,114],"__apple_namespac":115,llvm_parallel_compile_job:72,vec012:36,llvm_build_doc:72,unnamed_addr:[36,124],rival:20,rzi:11,param2:20,param1:20,"0x12345678":11
 5,sai:[25,29,102,51,114,113,7,28,26,127,107,15,63,36,27,78,4,94,20,21,23],nicer:[25,28,76,20],profiledata:36,argument:[],second_tru:36,sar:94,saw:[86,17,99,31],parseandsquartroot:20,entrytoken:94,notw:7,add_llvm_execut:81,xxxgenregisterinfo:66,wrapcolumn:76,destroi:[76,66,20,94,61,86,120,36,108],libpath:116,note:[],denomin:101,take:[48,101,0,88,76,49,50,2,125,96,111,55,78,5,6,7,62,9,102,85,10,94,11,113,59,115,87,61,123,15,81,16,17,18,19,20,21,22,23,24,25,26,84,66,114,82,27,28,29,30,31,32,33,86,34,36,68,90,120,99,103,38,92,119,40,93,42,58,121,53,122,75,43,97,124,57,127,46,128],multiarch:12,tolmach:82,jumptabl:36,printer:[],offload:54,mov32rm:83,buffer:[26,36,115,15,16,17,18,19,20,21,22,23,24,25,111,29,30,31,32,33,120,42,99,47],fcc_ug:66,compress:[38,72,42,124,55,20],private_segment_align:39,insertel:[],abus:20,homepag:[38,96],mov32ri:[83,94],allevi:[36,28,94,20],"_function_nam":35,drive:[44,40,52],fulldebug:[36,115],axi:1,salt:54,event:[0,102,40,42,97,72,20],p5600:[],merit:101,rodata
 :66,"__llvm_covmap":80,cclib:[18,19],objptr:36,slot:[],xmm:[36,7,66],slow:[86,38,36,42,74,87,20,62],host_x:14,activ:[101,58,82,36,42,94,61,43,97,120,20],v2size:58,freebsd5:94,host_i:14,sdk:[38,14],v16f32:36,assing:50,dominatortre:86,flagscpu1:76,clang:[],x86reloc:66,modulelevelpass:86,prime:[24,25,111,29,30,31,32,33,16,17,18,19,22,23],borrow:36,specialsquar:113,getframes:82,openorcreatefileforwrit:4,xmax:[18,32],clenumvalend:28,where:[],bpf_neg:94,compute_pgm_rsrc2_user_sgpr:39,sinbio:42,respres:20,deadlin:43,dw_at_apple_property_sett:115,callseq_start:40,arglist:36,xxxtrait:76,x86targetmachin:94,x24:121,build_mul:[16,17,18,19,23],getindex:66,unexpetedli:13,spars:[],screen:49,secnam:35,imm32:94,opval:66,sparc:[],uncondition:[25,58,59,94,35,36],genericvalu:[16,17,18,19],eflag:[83,47,8,128],do_safepoint:40,extern_weak:[36,124],mani:[100,48,73,1,49,40,51,26,101,96,3,111,4,7,9,108,57,94,11,113,36,115,60,12,61,13,14,15,81,16,17,18,19,20,21,22,23,66,114,82,27,28,29,30,31,32,33,86,88,70,38
 ,119,93,42,58,53,76,120,97,124,125,44,47],qhelpgener:72,dw_at_mips_linkage_nam:115,unistd:[4,5],sccp:[],constant:[],boat:101,xxxiter:20,printstar:[17,31],"200000e":[17,31],add16mr:8,image_scn_align_4096byt:121,afed8lhqlzfqjer0:43,ismod:128,parseifexpr:[24,25,31,32,33],inst_begin:20,add16mi:8,reflex:50,rss_limit_mb:42,constantfoldcal:57,symobl:35,thousand:48,release_15:38,ppcisellow:57,former:[40,42,94,53,123,63,83,111,22],getvaluetyp:66,combine1:94,combine2:94,emitalign:82,columnstart:80,polli:72,view_function_cfg:17,movsx16rm8w:94,chat:102,ctrl:24,lto_module_get_symbol_attribut:99,canon:[48,36,115,63,88,5,6,20],blah:[28,101,42],pthread:[14,36],ascii:[24,25,107,27,42,29,30,31,32,33,115,111,124,16,17,18,19,36,21,22,23],typedescriptor2:120,econom:102,binari:[],devcount:11,srem:[],p0v8i32:36,unhandl:120,irread:72,"0x1603020":109,getfunct:[24,25,82,29,30,31,32,33,86,20],extern:[],defi:36,sret:[36,124],defm:[],fnname:[24,25,111,29,30,31,32,33],dw_form_ref_udata:115,clobber:[],dereferenc:
 [],then_:[17,18,19],noencod:94,llvmlinkmodul:47,addmodul:[30,31,32,33,5,6,59,62,9],resp:[36,20],rest:[],checkcudaerror:11,fmadd:[47,94],gdb:[],unmaintain:8,invalid:[48,101,40,2,36,85,58,115,16,17,18,19,20,111,22,23,24,25,84,66,114,28,29,30,31,32,33,86,38,71,120,42,76,53,122,97],loadable_modul:[13,82,86],cond_fals:[19,33],r13w:8,"__builtin_trap":42,ghostli:20,"__imp_":36,littl:[],instrument:[80,48,114,42,122,105,3,125,36],r13d:8,r13b:8,exercis:[13,54,26,15,9],dwarfdebug:115,featurev8deprec:66,logallunhandlederror:[5,6],mrm2m:[66,128],around:[48,101,50,26,4,36,58,61,15,81,17,20,111,25,66,114,82,28,31,115,86,68,38,120,47,53,43,44,42],libm:[16,36,29,30,23],getunqu:20,unveil:[27,21],libz:36,traffic:[19,20,33],my86flag:76,llvm_lib:72,world:[],mrm2r:[66,128],find_program:72,intel:[],"__gxx_personality_v0":120,integ:[],timepassesisen:28,build_for_websit:104,inter:[3,71,58,47,43,63,4,36],orcremotetargetserv:5,manag:[100,102,49,40,26,104,96,5,6,59,62,9,85,58,36,108,15,19,20,66,114,82,30,31,32
 ,33,86,71,93,97,41,126],pushq:40,attrlist:34,a64:88,catchpad:[],llvmgetbitcodemoduleproviderincontext:[],handshak:42,pushf:94,pred_iter:20,constitut:[13,20,0,124,88],whould:0,stryjewski:48,exig:20,issiz:20,definit:[],exim:[],parseextern:[24,25,111,29,30,31,32,33],evolv:[80,43,99,102],noop:36,definin:[],nonintuit:56,notabl:[57,72,114,36,47,94,20],ddd:107,pointnum:82,power:[48,52,111,7,8,117,58,36,61,110,16,17,18,19,20,21,22,23,27,28,29,30,31,32,33,119,39,47,94,99],isloopinvari:20,blockaddress:36,image_sym_type_union:121,compileondemand:[6,59],n1984:101,n1987:101,n1986:101,ispic:66,standpoint:20,mov64rm:83,isset:28,mingw32msvc:94,acc:20,spiffygrep:28,gplv3:75,aco:58,acm:[82,94],printmethod:66,compuat:71,powerpc64:[117,36],cater:34,industri:56,rebuild:[],specialfp:128,cflag:64,surviv:[120,111,22],homeless:20,asymptomat:41,diflagfwddecl:36,basictyp:36,ehptr:120,hex:[],movsx64rr16:94,kaleidoscop:[],isloadfromstackslot:66,verbatim:[89,28,66],thedoclist:76,mantissa:36,conclud:[17,18,31,32]
 ,htpasswd:43,createjit:85,"__anon_expr":[24,25,111,29,30,31,32,33],clenumv:28,categor:[48,28,34,66],conclus:[],ifunequ:36,pull:[38,101,53,119],tripl:[],dirti:101,rage:55,agrep:51,image_sym_dtype_point:121,inaccuraci:36,emitprologu:66,reprimand:0,gcolumn:1,puls:42,gone:62,uid:107,creat:[],certain:[40,2,36,80,57,107,58,7,16,19,20,24,82,83,28,30,33,86,35,88,38,42,94,74,97,128],numregion:80,getnamedoperandidx:66,creal:[18,32],movsx32rr8:94,googl:119,discrimin:[94,101,36,113],extract:[],emphas:[101,127],collis:[36,101,20,115],writabl:[62,115],freestand:36,genuin:20,of_list:[16,17,18,19,22,23],rubi:82,benchspec:51,bpf_ldx:94,numexpress:80,spiffysh:28,allowsanysmalls:20,mask:[],shadowlist:66,tricki:[82,86,14,101,53],mimic:101,createuitofp:[24,25,29,30,31,32,33],prealloc:20,cpp:[101,1,50,4,5,6,59,62,9,57,11,7,115,108,109,13,81,20,111,24,25,112,66,82,28,29,30,31,32,33,86,34,38,72,42,94],cpu:[24,53,94,66,76,50,42,2,12,52,62,86,14,87,124,68,90,5,6,36,47],illustr:[88,27,28,29,115,33,86,99,111,3
 6,16,19,20,21,22,23],labeltyp:20,scc:[],dw_at_apple_properti:115,instrssrr:128,fntree:50,smp:[86,53],getnamewithprefix:[5,6,59,62,9],dw_lang_c99:[36,115],add16ri:8,incap:[26,15,124],add16rm:8,only_tool:[],intertwin:71,tail:[],add16rr:8,introduc:[48,40,104,5,6,36,62,9,113,58,7,61,8,50,17,18,19,20,66,31,32,33,47,94,53,97,128],getframeinfo:[94,66],"102kb":28,getaddress:[30,31,32,33,5,6,62,9],gcov_prefix_strip:105,candid:[],element_typ:[16,17,18,19,23],attr0:124,attr1:124,strang:[],condition:[82,2,81],release_xx:104,quux:101,colleagu:102,helloworld:81,pedant:72,sane:[27,72,21,53],initializeallasmpars:24,small:[101,40,51,104,55,4,36,80,56,11,41,13,63,81,50,20,21,25,113,114,82,27,28,115,86,90,93,42,94,122,43,97,124,44],release_xi:104,impract:20,stackgrowsdown:66,quicker:[0,52,62],"__image_info":36,sync:[38,76,53,11],past:[25,101,119,66,114,36,32,43,40,18,20,128],pass:[],fneg:36,deleg:[120,101,36,53],xor:[],registerregalloc:86,clock:[86,36],section:[],delet:[],succinct:2,letlist:46,contras
 t:[29,113,120,94,86,20,62,23],hasn:[86,20,62,114],full:[],hash:[],vtabl:[101,7,123],unmodifi:40,tailcal:94,r_offset:94,sol_socket:5,inher:[36,108,20,81],parenthesi:[111,101,22],islvalu:101,simpleproject:72,myownp3sett:115,shufflevector:[],prior:[80,38,120,28,94,61,86,43,124,44,36],lto_module_get_symbol_nam:99,pick:[],action:[38,57,101,0,119,66,120,36,94,86,3,40,5,6,20,62],narrowaddr:36,token_prec:[16,17,18,19,22,23],via:[],depart:[101,107],dw_tag_namespac:115,ifcond:[24,25,31,32,33,17,18,19],vim:[38,127,8],memrr:66,image_sym_class_member_of_union:121,ifcont:[24,25,31,32,33,17,18,19],unbias:70,decrement:120,select:[],x44:121,stdout:[38,42,121,105,96,16,17,18,19,36,22,23],llvm_doxygen_qch_filenam:72,googlesourc:42,"3dnowa":24,targetselect:[24,25,30,31,32,33,5],objectivec:36,isconst:[20,124],more:[],isintegerti:20,door:113,tester:[],hundr:63,hundt:14,sahf:94,zeroext:[36,124],worri:[25,119,38,28,36,111,22],addcom:82,webkit:[97,36],multiset:20,compani:43,cach:[125,53,58],uint64:[100,97],
 llvm_on_unix:4,enable_if:[111,113],sparcv8:[36,53],at_apple_properti:115,x86callingconv:66,leari:14,watcho:47,isnullvalu:50,returntyp:[82,36],learn:[38,101,102,119,50,47,26,127,33,15,36,19,20,62],cmpinst:20,legalizedag:57,bogu:[24,86],scan:[86,26,82,50,42,2,101,87,13,34,15,16,90,94,51],challeng:[40,18,101,32],registr:[],accept:[101,102,50,104,96,5,7,9,11,36,108,20,113,28,37,35,38,39,119,47,75,43,45,46,42,128],pessim:[100,48],x86instrinfo:66,badli:63,reconstruct:[115,107,114],transcendent:14,v_reg:94,newsockfd:5,huge:[38,101,13,34,43,8],llvmgrep:38,readobj:[],attrpchwrit:34,exprsymbol:[30,31,32,33],vla:[],clangxx:13,appenduniqu:36,simpl:[],prefetch:[],d14:66,plant:86,referenc:[50,36,115,16,17,18,19,20,111,22,23,24,25,66,83,28,29,30,31,32,33,37,71,99,75,123,124,46],spillalign:66,unfus:14,variant:[86,48,66,20,28,53,13,44,120,97,42,36,17,16,4,18,19,7,21,22,23],antisymmetri:50,unsound:[40,47],plane:[18,32],dllvm_use_sanit:42,maywritetomemori:[20,53],circumst:[66,7,30,33,86,36,120,16,19,2
 0],github:[65,42,20,119],arcanist:[],d13:66,llvmbitcod:57,imm_eq0:8,atan2:[27,21],nvidia:[14,94,11],returns_signed_char:36,"_flag":81,constitu:[17,31,120],ith:20,cc1:109,trade:[93,20,62],i386:[89,94,36],paper:[56,117,101,20,94],vec2:[36,20],vec0:36,vec1:[36,20],bou_unset:28,nifti:[86,17,26,15,31],bpf_jmp:94,alli:36,compilecallback:[5,6],bypass:[5,6,36,14],superflu:114,transformftor:62,targetselectiondag:[57,94,66],image_sym_type_void:121,cudamemcpi:14,argsv:[24,25,29,30,31,32,33],cond_next:[19,33],"__llvm":124,authent:[126,117],achiev:[],tokcodefrag:46,lto_module_is_object_file_in_memory_for_target:99,found:[48,73,1,49,40,2,104,96,55,78,4,7,62,9,56,94,11,36,115,12,13,14,18,19,20,64,23,24,25,66,82,28,29,30,31,32,33,86,107,38,41,72,92,93,42,58,76,43,120,99],gettermin:20,errata:117,bpf_mem:94,quesion:50,"0b000011":66,stringli:81,realli:[],loweralloc:86,getcalleesavedreg:66,reduct:[],reconstitut:36,ftp:[38,42],agre:[48,43,102,76],ftz:11,stackframes:82,research:[56,51,57],sparingli:63,x8
 6genregisterinfo:[94,66],occurr:[],ftl:[97,36],loopbb:[24,25,31,32,33],isfirstclasstyp:50,distoth:[],mrm0r:66,numabbrevop:124,believ:[101,0,102,36,30,31,32,43,16,17,18,20],"__cxa_begin_catch":120,mrm0m:66,wall:[26,86,2,15],fnptrval:36,prefac:81,getdebugloc:115,xxxend:20,advanc:[],struggl:38,amper:52,testament:[27,21],ge_missing_jmp_buf:101,new_then_bb:[17,18,19],cst_code_integ:124,instprint:34,dw_at_high_pc:115,curesult:11,only_ascii:42,unprofit:48,number:[],distchecktop:[],obj_root:38,horribl:101,dw_at_low_pc:115,differ:[],exponenti:[48,28,36],getpoint:36,checkpoint:120,unrecogniz:37,functionast:[24,25,111,29,30,31,32,33,5,6],illeg:[48,94,114,11,36,28,1,40,20,108],dfa:[94,34,118],fptr:25,relationship:[],meabi:87,bio_writ:42,compile_tim:51,dagarglist:46,consult:[38,71,72,107,56,96,86,14],compute_pgm_rsrc1_vgpr:39,aad:94,llvm_svn_rw:109,tokstr:46,seamlessli:99,reus:[94,115,86,43,97,81,36],arrang:[86,48,113,82,36,28,94,13,59],listen:5,cgft_objectfil:24,comput:[],packag:[],qpx:36,retur
 ns_twic:36,windbg:115,flto:[75,47,99,72],equival:[48,101,40,26,54,7,62,11,36,14,15,81,50,20,114,82,28,115,35,88,90,38,39,120,94,53,122,124,46,128],odd:[28,43,101,73],self:[],addrrr:66,gnuabi64:47,also:[],"__atomic_compare_exchange_n":53,ex2:11,ptrb:11,ptrc:11,coff:[],ptra:11,pipelin:[86,48,66,11,40,33,13,14,63,124,55,16,17,18,19,36],unset_vari:[],rhs_val:[16,17,18,19,23],plai:[27,26,86,15,50,46,21],"_z3foov":36,dstindex:66,plan:[],thecontext:[24,25,29,30,31,32,33],exn:36,ptr7:36,src_reg:94,"0x14c":121,ptr2:36,ptr3:36,ptr0:36,ptr1:36,ext:[36,88],abnorm:[4,63],exp:[],gabi:117,artem:14,rewritestatepointsforgc:[],pubnam:115,gold:[],getsymbolnam:66,xcode:[38,72,109],gcmetadaprint:82,session:[127,20,109],tracevalu:48,ugt:36,impact:[101,82,20,115,63,81,36],fputc:[24,25,30,31,32,33],cr0:36,cr7:36,addrri:66,writer:[],solut:[],printdatadirect:66,baseregisterinfo:34,llvm_executionengin:[16,17,18,19],factor:[101,1,20,94,36,8,128],bernstein:115,i64imm:66,llvm_obj_dir:[],microprocessor:[94,36,66]
 ,regstat:[83,94],tmp_clang:42,mainten:[78,43,99],noaa:[],r14b:8,f2_1:66,synthet:66,f2_2:66,synthes:[16,57,101,30,115],"__chkstk":35,machinememoperand:53,crc:42,coerce_offset0:7,link_compon:64,set:[],exec_tim:51,image_sym_class_member_of_enum:121,seq:121,creator:[86,72],overwhelm:[27,21],startup:[38,2,101,36],sex:102,cbpf:94,emac:[38,101,8],sed:[38,108],sec:36,sea:[117,39],overboard:101,analog:[82,20,86,120,40,36,9,128],v_mov_b32:39,reglist:66,llvm_external_project:72,parsenumberexpr:[24,25,111,29,30,31,32,33],lto_codegen_cr:99,topmost:82,pickup:38,mymaptyp:76,mutex:53,subdir:[],documentlisttrait:76,thrive:56,signatur:[38,94,107,40,29,53,86,88,55,36],machineoperand:[94,66],javascript:[36,26,15,97],libnam:[86,112],myocamlbuild:[16,17,18,19,23],disallow:[114,40,28,97,44,36],death:42,nohup:49,dividend:[14,94,36],proj_src_dir:[],sparctargetlow:66,last:[101,1,40,2,104,96,36,9,107,113,7,13,18,20,23,25,66,27,28,30,32,86,119,120,94,43,124,127,46,128],cmake_cxx_flags_relwithdebinfo:38,mmap:54
 ,whole:[48,101,50,51,54,36,62,9,57,107,12,13,123,63,16,17,20,22,82,111,30,31,86,68,120,42,94,43,125,44],pdb:115,partialalia:58,load:[],episod:[17,31],pointkind:82,dw_tag_namelist:115,hollow:76,lex:[25,27,16,17,18,19,46,21,22,23],thedoc:76,functionpass:[],"0x100000f24":89,"0xa":94,worthless:101,static_cast:[24,25,5,33],devic:[10,106,92,11,103,84,52,14],perpetu:43,sinc:[73,76,49,50,52,104,96,101,78,4,36,8,9,80,94,11,113,115,108,12,62,40,16,17,18,19,20,111,22,23,25,66,114,82,27,28,29,30,31,32,33,86,70,107,38,85,120,42,58,95,122,43,97,124,127,46,47],"0xe":124,xab:42,isstrongerthan:53,devis:[62,64],firm:[],squirrel:62,gettokpreced:[24,25,111,29,30,31,32,33],fire:[101,93],nologo:116,registerpass:86,rdtsc:36,educ:102,uncertain:101,straight:[94,58,40,27,111,68,14,9,50,4,128,20,21,22,23],corpora:[],histor:[101,114,20,125,13,81,36],durat:[86,94,58],passmanag:[],signature_invalid:38,error:[],dvariabl:72,v1size:58,pound:76,binutil:[126,38,117,12,75],genregisternam:94,miscommun:43,inst_invok:124
 ,vectorcal:[],chase:73,i29:36,llvmparsebitcod:47,irrelev:[114,58],initializerconst:36,i20:36,i24:36,x64:[126,38,54,7],shorter:[43,122],funni:[19,33],decod:[],dllvm_enable_sphinx:38,built_sourc:[],boringssl:42,global_end:20,bitread:44,atomic_load_:53,image_sym_class_union_tag:121,dw_at_declar:115,stack:[],recent:[38,72,119,49,120,42,76,30,82,43,36,47,9],knl:47,call32r:128,eleg:[111,26,30,31,15,16,17,22],rdi:[83,94,36,8,97],dw_apple_property_readwrit:115,llvm_unreach:[50,5,101,20],person:[],parse_prototyp:[16,17,18,19,22,23],expens:[100,48,101,72,66,50,28,53,86,14,120,20,42],call32m:128,llvm_tablegen:72,always_inlin:[],crosscompil:[94,12],else_v:[17,18,19],immutablepass:[],use_trac:42,debug_level:28,simd:[90,87,36,1],numshadowbyt:97,sidebar:104,mandat:94,smooshlab:56,eager:[20,62],fnast:[24,25,29,30,31,32,33,5,6],cmpxchg16b:54,input:[],saniti:[44,38,42,63],transpar:[57,101,114,20,28,99,47],subfield:128,intuit:36,dw_tag_ptr_to_member_typ:[36,115],"0x00000048c979":42,formal:[0,36,50,20,
 8,128],llvmgettargetmachinedata:47,todefin:34,atomicexpand:53,ivar:115,stylist:101,funcresolv:20,image_sym_type_nul:121,parse_toplevel:[16,17,18,19,22,23],ii32:128,x86framelow:94,moduleid:[13,29,23],encount:[66,20,94,37,63,120,36,62,9],image_file_debug_strip:121,acknowledg:0,sampl:[],sight:[19,33],itanium_abi_tripl:13,attrvisitor:34,compilelay:[5,6,59,62,9],libssl:42,"_bool":[19,33],p5i8:11,religion:102,llvm_obj_root:[13,51,64],xxxgendagisel:66,reloc:[],agreement:43,wget:[38,42],sub:[],materi:[50,102],codeemittergen:34,image_sym_type_long:121,condbranch:66,intd:7,oneormor:28,getinsertblock:[24,25,31,32,33],putchard:[24,25,26,30,31,32,33,15,16,17,18,19],primarili:[38,10,60,48,82,42,2,52,32,61,67,44,18,94,20,69,128],getimm:66,xxxinstrformat:66,requires_rtti:74,contributor:[125,43,72,81],volcan:39,pcre:42,occupi:[94,36,107],span:[86,101,8],kaleidoscopejit:[],submit:[],custom:[],createcondbr:[24,25,31,32,33],parse_arg:[16,17,18,19,22,23],expound:[],subgraph:48,poster:102,atop:82,nodupl:
 36,atoi:36,link:[],atom:[],line:[],bpf_exit:94,workitem_vgpr_count:39,cie:71,cin:108,intim:101,hex8:76,"0xffffffff":[94,36,124],pointi:76,copy_:[],chao:125,call_site_num:120,"char":[101,1,111,5,36,9,80,107,11,115,109,14,16,17,18,19,20,21,22,23,24,25,66,114,28,29,30,31,32,33,86,42,58,99],superscalar:14,srcvalu:40,linkonceodrlinkag:20,tok_unari:[24,25,32,33],intrepid:[111,22],int32ti:20,xxxcodeemitt:66,ud2a:94,kwalifi:121,scrape:2,download_prerequisit:38,cleanupret:[],disp32:94,isnotduplic:8,"0x000000000059c583":109,caml:[],lang:28,mayalia:58,land:[120,40,47,61,43,83,36],x86codeemitt:66,algorithm:[],agg:36,libstdc:[38,47,101,12],fresh:[38,42],hello:[],mustalia:58,llvmcontext:[],code:[],partial:[],resultv:36,scratch:[36,94,20,66],personalityfn:124,setcc:[94,20],globallisttyp:20,quarantin:54,printimplicitdef:66,young:20,send:[],tr1:20,sens:[29,72,107,108,58,36,28,26,61,53,115,101,15,40,114,94,20,42,9,23],getprocesstripl:25,sent:[56,43,119,103,104,87,40,122],xxpermdi:[],ddi0403:117,unzip
 :[49,38],flagscpumask:76,clearresourc:94,registeredarg:82,setmaxatomicsizeinbitssupport:53,tri:[48,72,66,50,42,94,30,93,86,27,127,36,21],bsd4:107,setconvertact:66,dname:28,libfil:112,trc:94,scalabl:58,tre:48,fewer:[82,48,40],"try":[],race:[36,54,20,53,102],build_uitofp:[16,17,18,19,23],vehicl:[101,81],use_s:20,dclang_enable_bootstrap:125,monospac:127,natur:[],odr:36,proj_obj_dir:[],psubu:13,n64:47,video:[20,102],ueq:[19,36,33],index:[],step_val:[17,18,19],tdm:126,targetregisterclass:[94,66],skylak:47,asmwrit:[],test_fuzz:42,henceforth:[95,36],paramti:124,image_scn_align_64byt:121,dyn_cast_or_nul:20,lllexer:57,leb:80,dw_tag_gnu_template_param_pack:36,mappingtrait:76,len:36,bitstreamwrit:57,rglob:10,let:[],ubuntu:[38,47,12,52],ptx30:94,openmp:[38,43],maken:5,great:[101,82,27,94,32,86,43,63,125,18,20,21],survei:117,dllvm_enable_doxygen:72,oneargfprw:128,force_off:72,technolog:[99,47,26,15],rdx:[40,94,97,8],flagshollow:76,cta:11,ifloc:25,qualifi:[],sgt:36,pf1:50,pf0:50,dfpregsregistercl
 ass:66,sgn:36,llvm_enable_cxx1i:72,sge:36,movsx32rr16:94,"__________":20,getnumparam:20,eltti:[25,124],zip:38,commun:[],my_fmad:11,doubl:[48,76,50,26,54,111,5,7,117,113,36,15,16,17,18,19,20,21,22,23,24,25,66,27,28,29,30,31,32,33,94,96,124,128],upgrad:[],next:[],doubt:[127,113],lock:[86,36,20,63,53],commut:[48,94,66,58],fpregsclass:66,avx512:[47,36],gladli:[38,96],p2align:39,firstcondit:20,bunzip2:38,objectslo:[],uvari:72,get_instrinfo_operand_enum:66,safepoint_pol:40,devmajor:11,erasur:20,intregssuperregclass:66,thin:[116,72,47,20],optimizelay:[5,6,59,62],gc_root:40,statepoint_token:40,dw_form_data4:115,n2431:101,weaker:36,dw_form_data1:115,dw_form_data2:115,n2437:101,process:[],n2439:101,preformat:127,high:[],wavefront_s:39,fprintf:[24,25,111,29,30,31,32,33],streamer:94,dw_ate_signed_char:36,onlin:[81,19,72,33],adc32mi8:8,visitsrl:57,delai:[20,47,0,50],infeas:71,allocainst:[24,25,101,36,33,19,20],cuda:[],nullpointerexcept:100,overridden:[],singular:[101,20],surfac:94,xc3:121,loc0:9
 7,loc1:97,xc7:121,xc4:121,x86registerinfo:[94,66],optyp:66,dw_tag_class_typ:[36,115],some_var:81,essenti:[66,82,20,84,53,124,50,46],sdiv:[],seriou:0,counter:[],robot:56,element:[],at_typ:115,unaccept:43,allow:[],retval:[24,25,120,29,30,31,32,33,36],stepexpr:[24,25,31,32,33,19],movl:[36,7,97,40],decltyp:[101,36,5,6,59,62,9],fstrict:36,movi:101,typecod:57,insight:[80,36],stacksav:[],vma:[],evolutionari:42,movz:[36,88],movw:[36,35],movt:35,ofstream:28,ldpxpost:83,movq:[40,97],perfect:[43,88],chosen:[101,82,2,88,94,36],cond_tru:[19,33],lastinst:66,decad:8,therefor:[80,48,76,114,11,82,36,28,94,53,115,86,43,97,88,120,45,20],python:[38,26,49,42,2,12,13,82,96,15,46,51],initializenativetarget:[25,30,31,32,33,5],overal:[119,114,82,120,94,31,34,43,17,36],innermost:1,facilit:[101,20,76,115,43,36,64],gcodeview:115,add32rr:8,fcc_val:66,anyth:[38,101,113,108,48,36,87,94,30,31,53,115,96,43,97,90,16,17,20,8,23],cross_ov:[],xvjf:38,truth:[17,36,31],"0b111":128,llvminitializesparcasmprint:66,compute_x
 x:11,idxmask:36,subset:[26,114,11,36,51,2,58,53,13,43,15,97,20,115],"0x7fffffffe040":109,bump:[82,95,20],"0x400":115,lsampl:64,"static":[],uiuc:43,unique_ptr:[24,25,59,111,29,30,31,32,33,5,6,20,62,9],variabl:[],contigu:[36,20,115],possbil:76,tok_if:[24,25,31,32,33],tok_in:[24,25,31,32,33],dw_tag_shared_typ:115,shut:[42,101,66],initializepass:58,bpf_dw:94,unpars:[111,2,22],tempt:[4,101,38],image_file_system:121,greedi:[94,28,87],bam:101,image_sym_class_sect:121,spill:[40,94,97,66,90],"__atomic_fetch_xor_n":53,unnam:[48,101,36,28,83,46],area:[],scari:[27,26,15,21],length:[],enforc:[101,0,82,20,28,94,53,43,97,36,7,128],outsid:[],scare:43,noitinerari:[8,66],softwar:[],"__profn_foo":80,denorm:[14,76,36],add_pt:78,spaghetti:[27,21],selectiondagnod:66,fcontext:25,owner:[],stringswitch:[47,34],add_pf:78,featurev9:66,sparcgensubtarget:66,licens:[],system:[],parse_oper:[18,19],gcse:[86,48,20],termin:[],f_inlined_into_main:89,erron:[38,28],low:[],ldrex:53,expraddr:5,gotcha:[101,81],alloc:[],ba
 seclasslist:46,third_parti:42,"12x10":36,haven:[101,51,86,96,5,6,36,9],"0x40":115,bother:[19,62,33],fcc_u:66,"__llvm_coverage_map":80,featurevi:66,cgit:[],stricter:[7,53],f1f2:50,xxxregisterinfo:66,tdtag:34,getzextvalu:20,terribl:125,viewer:101,op_end:20,var_arg_function_typ:23,clearli:[97,43,101,115],optimis:16,mdstring:3,"0x00002200":115,tramp1:36,accuraci:[48,36],add_llvm_unittest:72,executeremoteexpr:5,amdfam10:24,type_of:[16,17,18,19,23],courtesi:43,griddim:11,poison4:36,poison3:36,poison2:36,aarch32:117,incfil:[],setloadextact:66,placement:[],stronger:[36,20,53,40],parsevarexpr:[24,25,33],face:[101,95,86,34,63,4],isbranch:8,brew:20,sqrtorerr:20,linkonc:[],fact:[101,0,26,59,107,58,36,108,14,15,63,16,18,19,20,113,114,28,30,32,33,86,38,71,120,94,43,44,46,128],movslq:97,dbn:38,borderlin:101,truedest:36,dbg:[],bring:[101,82,40,26,15,63,20,9],rough:[42,128,46,114],trivial:[],redirect:[25,41,42,104,13,123,36],roots_end:82,getelementptr:[],hash_data_count:115,"0x01":[80,8,115],should:
 [],jan:107,jal:[],tape:38,create_funct:[16,17,18,19],opreand:20,hope:[101,82,50,42,74,43,40,47],meant:[80,46,0,38,49,50,84,96,56,36,127,20,128],move:[],familiar:[25,113,39,11,27,94,31,86,14,120,63,38,50,17,21,9],memcpi:[],autom:[38,119,94,34,43,125,8,64],smash:36,isatleastreleas:[],symtab:20,ptr_rc:94,reid:4,dw_ate_sign:[36,115],stuff:[],booltmp:[24,25,29,30,31,32,33,16,17,18,19,23],tok_def:[24,25,27,111,29,30,31,32,33],comma:[20,28,76,31,13,36,17,45,7,128],unimport:[49,40],cmake_cxx_compil:38,symbolt:20,rtdyldmemorymanag:[5,6,59,62,9],temporarili:93,binary_nam:89,oprofil:[74,72],wire:108,op_iter:20,fakesourc:[],live_iter:82,sectionmemorymanag:[85,5,6,59,62,9],unrecurs:[24,25,19,33],email:[56,71,0,102,119,38,26,53,43,15],superword:[71,1],dislik:43,linkonceanylinkag:20,memri:[94,66],use_iter:20,doxygen:[],scalaropt:112,valgrind:[13,41,2,73],sdtc:66,etc:[],shouldinsertfencesforatom:53,vk_basicblock:101,preheader_bb:[17,18],position_at_end:[16,17,18,19,23],exprprec:[24,25,111,29,30,31,
 32,33],distil:13,bininteg:46,rpcc:36,escudo:54,chromium:[42,47],v8p0f32:36,llvm_external_:72,triniti:117,insuffici:[4,36,52,66,115],path_to_llvm:38,immedi:[],hex16:76,deliber:[101,97],image_sym_type_char:121,togeth:[48,101,1,50,51,7,80,107,58,36,13,20,111,29,82,27,28,84,31,32,115,86,37,88,70,41,92,93,42,94,122,43,120,44,128],allocationinst:20,my_jit_tool:[],sphinx_output_man:72,rbx:[94,8],dataflow:[19,36,33],cvt:11,reloc_absolute_dword:66,rbp:[94,8],suport:[],llvm_tools_binary_dir:72,p0f_isvoidf:40,cve:42,"__sync_fetch_and_sub_n":53,lto_module_create_from_memori:99,immtyp:8,"__sync_fetch_and_min_n":53,libxml2:[42,12],apfloat:[24,25,38,29,30,31,32,33,23],site:[],axpi:14,archiv:[],createlambdaresolv:[5,6,59,62,9],incom:[66,36,94,31,33,43,17,18,19,20],surprisingli:[38,111,30,63,16,22],uncategor:28,mutat:[],referenti:48,basicblocklisttyp:20,intra:58,lex_com:[16,17,18,19,21,22,23],android:47,dan:76,preserve_mostcc:[36,124],phi:[],kernarg_segment_align:39,expans:[80,94,66,36,68,53,105,63,
 81,46,83],upon:[85,66,82,20,84,115,43,36,64],foldmemoryoperand:[94,66],setbann:5,php:119,expand:[],"__sync_fetch_and_max_n":53,off:[101,0,40,26,52,36,8,9,107,11,62,13,14,15,16,17,18,19,20,21,23,24,25,27,29,30,31,32,33,38,72,93,47,94,74,43],symbol2:35,diversifi:[],call2:7,argnam:[24,25,28,29,30,31,32,33,111],a_ctor_bas:7,command:[],filesystem:[24,2,12],outputfilenam:28,newest:[35,30],ptrval:36,less:[48,101,49,50,26,52,105,111,36,8,80,107,58,115,108,61,13,15,63,40,16,17,18,19,20,21,22,23,24,25,2,82,27,28,29,30,31,32,33,88,38,42,94,43,124,127],sharedfnast:[5,6],value_2:44,web:[],makefil:[],blockfrequencyinfo:[56,70],exempt:101,ptx31:94,target_opt:[],nonnul:[120,36,63],nvt:66,unintrus:36,indvar:[],goingn:20,piec:[101,94,104,96,36,115,13,63,81,17,18,19,93,21,22,23,25,114,27,111,29,31,32,33,38,42,73,43,124,44,128],placesafepoint:[],core2:13,five:[120,28,94,30,20,62],release_16:38,password:[126,43],recurs:[48,29,82,27,111,2,31,32,33,34,15,36,40,17,18,19,20,21,22,23],recurr:48,desc:[86,5,28
 ,66],addsdrm:128,resid:[124,11,82,42,94,115,86,88,36],emmc:52,loopinfobas:20,isus:94,objectbuff:85,byteswap:57,resiz:101,"0x29273623":115,captur:[26,5,6,7,62,57,36,115,13,15,16,17,18,19,93,111,22,23,24,25,28,29,30,31,32,33,94,97,124],vsx:36,main_loop:[16,17,18,19,22,23],build_exampl:[],mem2ref:40,i64:[80,66,11,36,94,115,123,3,97,88,40,114,7,8],i65:36,safepoint_token:40,flush:[24,85,101,11,52,14,16,17,18,19,36,22,23],guarante:[],ltmp1:40,"__syncthread":11,avoid:[],image_sym_class_fil:121,arg_siz:[24,25,82,29,30,31,32,33,20],barlist:101,multidimension:36,stage:[],"0x4200":115,c_str:[24,25,11,27,28,29,30,31,32,33,20,111],interven:97,nullari:[111,22],declcontext:113,dw_op_deref:36,getbitwidth:20,ccinfo:[5,6],not_nul:100,handleextern:[24,25,111,29,30,31,32,33],dw_tag_base_typ:[36,115],dereferenceable_byt:36,retcc_x86_32:66,takecallback:20,waterfal:126,mere:[48,119,114,40,29,96,36,23],merg:[],ifuncti:36,createsubroutinetyp:25,relpo:107,valuesuffix:46,multidef:128,textfileread:101,intellig
 :[36,20],p4i8:11,mandel:[18,32],mdnode:[3,36],"function":[],namedvalu:[24,25,29,30,31,32,33],foldingsetnod:20,innoc:[17,31],documentlist:76,getenv:4,dw_at_entry_pc:115,inst_cal:124,data16bitsdirect:66,lookup_funct:[16,17,18,19,23],evidenc:114,localexec:[36,124],llvmcreateexecutionengin:[],otherwis:[48,101,0,120,76,50,2,52,104,105,111,55,7,62,80,10,106,36,60,12,63,40,16,17,18,19,20,21,22,23,24,25,112,84,67,82,27,28,29,30,31,32,33,86,87,90,69,70,103,41,71,72,92,39,93,73,53,99,124,125,98,118,46,128],problem:[],"int":[101,1,50,26,96,78,5,7,8,9,80,94,11,36,115,108,61,109,14,15,40,16,17,18,19,20,111,22,23,24,25,66,114,82,27,28,29,30,31,32,33,88,89,38,41,93,42,58,121,53,76,75,99,120,127,46,128],filenam:[80,118,10,101,72,92,106,7,28,84,112,122,103,87,55,90,69,37,79,41,98],inl:14,jessi:12,rightli:[],ini:44,ind:25,inf:[90,28,87,36,115],ing:[48,101,29,33,16,19,23],inc:[38,66,83,94,86,89,34,78],filenameindex0:80,bzip2:38,nonetheless:[36,5,6,59,62],cudadevicesynchron:14,libcxx:[49,38],lookup:[],
 eabi:[47,87],varieti:[101,26,52,117,107,58,15,81,16,17,18,20,23,82,29,30,31,32,115,38,71,120,42,94,53,97,124,44,46,47],deadli:42,liblzma:12,computearea:113,aliasresult:58,"__cxa_allocate_except":120,potenti:[48,101,0,40,2,104,54,111,36,58,108,123,63,17,93,21,22,27,28,31,38,120,42,94,43,97],kernarg_segment_byte_s:39,emitsymbolattribut:94,fexist:50,in0:36,in1:[94,36],in2:94,eof:[24,25,27,42,29,30,31,32,33,111],header_data:115,cumemfre:11,orcremotetargetcli:5,rule:[],"__sync_":[],configmaxtest:20,hashes_count:115,sourceloc:25,sm_20:[94,11],sm_21:94,untrust:43,"0x16151f0":109,show_bug:42,oldest:30,"const":[],r8b:8,r8d:8,deviat:[94,101,35],binoppreced:[24,25,111,29,30,31,32,33],worth:[101,113,20,52,63,93],r8w:8,rowfield:78,hasfparmv8:8,printnextinstruct:20,my_list:81,getpar:[24,25,31,32,33,20],image_scn_mem_not_cach:121,ccmgrorerr:5,shoot:[16,30],llvm_enable_ffi:72,cmd:119,issimpl:53,upload:[119,104],defens:43,mllvm:1,unmanag:[40,36],math:[],add_rr:128,add_char:[16,17,18,19,21,22,23],ext
 ernally_initi:[36,124],callcount:20,eretnc:[],cmp:[48,42,94,20,36],pty:36,soutbio:42,hork:128,consequ:[38,102,58,36,42,53,93,13,97,120,20],image_scn_mem_shar:121,llvmbuild:[],insid:[48,101,76,49,50,51,2,5,6,36,62,9,80,56,12,109,13,81,20,113,67,82,30,115,86,34,72,40,120,42,94,123,124,46,47,128],renderscript:[],loop_bb:[17,18,19],flaghollow:76,sockfd:5,topolog:7,told:101,ontwo:36,somefunc:[101,20],mcoperand:94,pred_end:20,dw_op_bit_piec:36,"_ri":128,addrorerr:5,dw_virtuality_pure_virtu:36,optzn:[73,30,31,32,33,16,17,18,19],"0f7f800000":11,aka:[36,58,16,17,18,19,20,21,22,23,24,25,27,111,29,30,31,32,33,42,94,125],werror:75,dcmake_cxx_link_flag:38,idnam:[24,25,111,29,30,31,32,33],instr:[80,72,82,94,122,105,118,128],setgc:82,sspstrong:36,ftoi:66,total:[48,124,50,42,95,53,115,86,36,55,20,51],bra:11,highli:[82,20,42,94,33,63,36,19,59,64],bookkeep:[48,20],plot:[18,32],postincr:101,insult:102,deref_bytes_nod:36,foster:[4,43],shortest:[50,46],simplifycfg:[],setreg:94,v_mul_i32_i24_e32:39,iscom
 mut:8,rediscov:[26,15],reinterpret:88,numberofauxsymbol:121,toolkit:[20,11],tblegen:34,valueenumer:57,armgenasmmatch:34,springer:14,insignific:[97,60,36],err:[24,102,11,42,86,5,6,20],restor:[24,25,66,61,94,95,31,32,33,124,120,17,18,19,36],next_prec:[16,17,18,19,22,23],work:[],foo_ctor:61,coalesc:[90,60,20,94],noreg:83,viewcfgonli:[20,31],runtimevers:[36,115],could:[],"16gb":126,novic:72,autodetect:[90,87,105],dllvm_enable_assert:[38,42,52],u64:11,indic:[],somefil:[],deepcheck:20,unavail:[53,66],constantstruct:20,getloopanalysisusag:86,indir:42,createinstructioncombiningpass:[30,31,32,33,5,6,59,62],str2:128,ordinari:[80,76,36],lexloc:25,march:[24,38,83,47,73,12,115,87,90,7],sever:[48,101,0,49,50,51,26,54,55,4,36,8,80,56,57,107,58,13,14,15,81,17,20,64,23,2,66,82,83,28,29,31,115,86,34,68,38,72,92,119,93,42,94,122,124,120,99,47,128],verifi:[],"__atomic_fetch_add_n":53,bindir:112,ssl_set_bio:42,recogn:[25,51,48,27,28,94,31,99,50,17,36,21],superreg:66,rebas:38,lad:28,chines:38,after:[],he
 x32:76,lab:[126,56,42],createlocalindirectstubsmanagerbuild:[6,59],endcod:101,law:[101,0],demonstr:[80,113,66,36,29,30,16,20,23],sparccallingconv:66,domin:[],sgpr:36,opaqu:[],lto_module_dispos:99,kdatalen:14,recompil:[100,58,31,97,88,17],icmpinst:20,buildslav:126,spilt:94,order:[],movhpd:7,hex64:76,diagnos:[86,60,1],use_camlp4:[16,17,18,19,22,23],offici:[],opnod:66,llvmsystem:[],pascal:36,noimm:8,incid:0,getnexttoken:[24,25,111,29,30,31,32,33],flexibl:[],getattribut:50,bytecod:124,isascii:[24,25,111,29,30,31,32,33],isellow:[34,53],initialexec:[36,124],setoperationact:[94,53,66],mips64r2:47,them:[48,101,0,102,76,49,50,51,26,105,96,111,78,4,5,7,62,9,80,94,11,113,36,115,108,12,116,13,14,15,63,81,16,17,18,19,20,21,22,23,25,66,114,82,27,28,29,30,31,32,33,86,37,88,68,120,107,38,41,72,92,119,40,93,47,58,95,53,122,74,43,97,64,124,83,44,45,99,128],dw_apple_property_atom:115,thei:[100,48,101,0,102,1,49,50,51,26,52,104,96,111,55,78,4,6,7,8,9,80,56,107,58,113,36,115,60,61,62,13,14,15,63,81,16,1
 7,19,20,108,22,23,84,2,66,114,82,83,28,29,30,31,33,86,34,88,90,37,38,41,71,72,119,122,40,93,42,94,53,76,43,97,64,124,120,44,45,47,128],fragment:[67,82,40,51,94,115,36,128,46,20],safe:[],printccoperand:66,scene:20,"break":[],bang:46,astread:34,selti:36,lifelong:56,stdarg:36,changelog:42,"__cxa_rethrow":120,sequentialtyp:20,myerror:20,monolith:[43,95],"0x000003cd":115,const_op_iter:20,network:[42,94,20],fuzzinglibc:42,visiticmpinst:93,suffic:88,addxri:83,lib64:[38,14,72],forth:[53,88],image_file_relocs_strip:121,multilin:[2,46,128],"_ty":57,srcmakefil:[],registeralias:34,ms_abi_tripl:13,barrier:[],multilib:12,standard:[],nth:101,fixm:[38,0,66],shadowstackgclow:82,debuglev:28,mvt:[94,66],angl:[101,76],zerodirect:66,regress:[],gcregistri:82,subtl:[114,42,26,31,15,81,16,17,111,22],refil:50,render:[36,18,94,20,32],printdeclar:66,subreg:66,i48:36,setcondcodeact:66,llvm_build_32_bit:72,"0x00000000016677e0":109,ispredic:8,libllvmir:20,image_file_bytes_reversed_hi:121,r_amdgpu_rel32:94,isalph
 a:[24,25,27,111,29,30,31,32,33],baseclasslistn:46,john:[43,101],"40th":[27,21],headerdata:115,getdatasect:82,inexact:36,still_poison:36,registerpasspars:86,gcmetadataprinterregistri:82,happili:30,analyzebranch:66,tex:51,llvm_build_root:72,llvmgcc:[],target:[],provid:[],cppflag:64,minut:38,uint64_t:[50,76,68,5,20,70],hassse2:128,hassse3:128,emitfunctionstub:66,contenti:101,n1737:101,manner:[80,102,66,114,120,20,42,94,53,43,40,36],reali:42,strength:[],recreat:[38,76,36],is_nul:100,laden:[26,15],latter:[66,50,42,94,53,36,40,20,111,22],image_rel_amd64_secrel:35,enablecompilecallback:5,"0x400528":89,"__attribute__":14,llvm_doxygen_qhp_namespac:72,smul_lohi:94,initializemoduleandpassmanag:[24,30,31,32,33],bruce:20,cumodul:11,llvm_definit:72,lexic:[],endexpr:[24,25,31,32,33,19],keystrok:101,retcc_sparc32:66,passthru:36,inc32r:83,excus:102,valuerequir:28,instritinclass:8,bracket:[101,83,76,115,43,120,44,36],unchang:[36,5,6,20,58],notion:[101,113,94,30,31,115,86,43,16,17,36],bpf_jeq:94,md_pr
 of:3,opposit:[71,20,107,76],tailcallopt:[94,36],buildbot:[],op0:124,involv:[48,101,0,76,40,104,54,78,4,36,57,58,63,17,19,20,22,25,66,114,82,111,31,33,70,72,94,53],latent:42,op2:36,the_funct:[16,17,18,19,23],"41m":28,wzr:36,sroa:[14,71,63,53],baseopcod:[78,66],latenc:[90,94,36],callbackvh:20,govern:36,instlisttyp:20,predecessor:[],showdebug:109,likewis:[38,36],"0cleanup":120,llvm_include_tool:72,subtarget:[],didescriptor:115,numregionarrai:80,lit_arg:13,fomit:94,isosdarwin:25,emb:[36,26,15,124],cstdint:[30,31,32,33],targetaddress:[5,6,59],cleanli:[86,36,43,101,104],st_uid:107,cudevicegetcount:11,strncmp:42,commandlin:[],memorywithorigin:72,"0x60500020":121,movsx32rm16:94,chapuni:56,dw_ate_float:[25,36],eatomtypedieoffset:115,awar:[],sphinxquickstarttempl:127,unordered_set:20,awai:[48,101,113,82,7,115,21,86,70,99,36,27,20,62],getiniti:20,accord:[76,113,66,49,36,28,29,104,82,97,124,40,20,70],unsett:86,smallsetvector:20,preprocessor:[80,108,72,66,28,26,30,105,14,15,16,20],isjumptableind
 ex:66,setsockopt:5,image_file_machine_armnt:121,cov:[],howev:[100,101,1,40,51,26,78,4,59,8,9,85,107,58,36,115,108,12,61,62,13,15,16,17,18,19,20,114,82,83,28,29,30,31,32,33,86,35,88,38,119,93,42,94,95,53,74,75,43,97,124,120,44,127,47],shouldn:[85,101,58,27,28,12,36,21],jitcompilerfn:66,calltmp:[24,25,29,30,31,32,33,16,17,18,19,23],ilp:1,xmm6:[8,128],com:[38,101,117,119,65,42,116,43,20],ctxt:76,con:[46,88],testcleanup:36,widen:[94,36,1],xmm4:[8,128],resultti:36,i8086:24,trunk:[38,119,51,56,42,94,96,104,13,14,43,47,115],getbasicblocklist:[24,25,31,32,33,20],permut:36,prologu:[],wider:[57,53,114],add_instruction_combin:[16,17,18,19],xmm8:8,speak:[0,102,40,31,32,81,17,18],degener:[48,19,33],"__builtin_expect":3,internalread:83,macport:74,debug_info:115,subscrib:[43,119],mallocbench:51,mainfun:5,compatible_class:94,machineblockfrequencyinfo:70,hoist:[48,20,53,97,58],unclutt:4,dwoid:36,binaryoper:[101,20],inhibit:[36,122],ident:[48,101,0,102,50,36,107,58,7,115,12,13,16,17,18,19,20,21,22,23
 ,82,83,30,31,33,88,94,123,125],aix:[94,117],gnu:[24,38,101,72,107,66,120,42,94,52,86,75,87,125,126,37,36,128],mitig:[82,54],zlib:[13,38,72],cxx_statu:101,aim:[80,41,101,0,36,14,93,54,43,88,81,4,20,9],scalarrepl:[],pairwis:58,publicli:[20,0,115],aid:[82,36],vagu:43,keytyp:115,ispack:124,u999999:119,xstep:[18,32],printabl:[36,107,66],conv:108,theexecutionengin:[25,33],harddriv:52,sockaddr_in:5,extractloop:48,shadowstackgc:82,uint32x2_t:88,cond:[24,25,66,108,31,32,33,17,18,19,36,70],succee:30,dw_tag_label:115,dumper:[115,122],old_val:[17,18,19],descent:[27,111,32,18,21,22],incorrectli:[27,29,23],perform:[],descend:[120,36],doxgyen:72,addintervalsforspil:94,fragil:[],code_own:[43,119],evil:[20,8,88],hand:[48,101,0,76,49,50,4,8,113,15,16,18,20,21,22,23,66,114,82,27,111,29,30,32,34,68,94,53],fuse:[48,14,36,90],llvmaddtargetdata:47,use_llvm_scalar_opt:[16,17,18,19],disassembleremitt:34,operandv:[24,25,32,33],kept:[71,0,58,42,101,86,43],undesir:36,scenario:[38,93,108,53,13,125,20],thu:[48,1
 01,50,36,80,94,58,115,108,13,63,40,16,17,18,19,20,111,22,23,24,25,82,28,29,30,31,32,33,86,70,119,93,42,73,53,43,124,120],hypothet:[40,50,94,86,120,20],whizbang:101,get_reginfo_target_desc:34,contact:[0,102,42,86,43,126,47],thi:[],gettok:[24,25,27,111,29,30,31,32,33],clenumvaln:28,value_load:36,destsharedlib:[],mcompact:47,basetyp:36,mandelbrot:[27,18,21,32],stack_loc:94,ifdef:[80,28,26,15,4,42],sparctargetasminfo:66,getkei:20,lowertypetest:123,opencl:[39,11],spread:48,board:[12,43,0,52],parse_primari:[16,17,18,19,22,23],relwithdebinfo:[38,72],mayb:[34,26,15,42,57],stringwithspecialstr:115,fusion:36,fsin:[87,66],startval:[24,25,31,32,33],ppc32:94,bpf:[38,42,94],sectnam:28,p3i8:11,bucket_count:115,bpl:8,rvalu:101,image_file_machine_ebc:121,openfil:101,prefixdata:124,manual:[],percentag:55,cfrac:51,bork:[28,128],flatten:[94,36,1],rl247416:42,rl247417:42,rl247414:42,pos2:28,pos1:28,getmodulematchqu:66,colloqui:36,fpic:72,loadregfromaddr:66,mandleconverg:[],dopartialredundancyelimin:28,p
 eek:[16,17,18,19,22,23],plu:[124,66,82,36,111,31,115,43,88,120,17,20,62,22],aggress:[],memdep:[],someclass:46,pose:[82,71],confer:[82,94],"1cleanup":120,fastmath:11,repositori:[38,119,56,120,42,73,12,115,13,43],post:[],bpf_mov:94,obj:[112,49,40,51,115,82,96,87,120,89,36],literatur:94,image_scn_align_4byt:121,gc_transition_end:40,canonic:[],s64:11,deltalinestart:80,nctaid:11,sames:36,curiou:50,xyz:[78,90,87],"float":[],profession:43,bound:[],opportun:[48,66,1,30,63,16,36,62],accordingli:[78,36,20,82,120],wai:[],copycost:66,callexprast:[24,25,111,29,30,31,32,33],n2764:101,formul:4,lowest:[24,25,101,111,29,30,31,32,33,80,88,53,16,17,18,19,36,22,23],asmwriternum:118,raw_ostream:[],end_amd_kernel_code_t:39,somehow:[86,20],llvmlinkmodules2:[],"true":[48,101,76,50,52,54,3,78,5,6,59,8,9,94,11,113,36,115,12,62,13,81,16,17,18,19,20,111,23,24,25,66,114,82,83,28,29,30,31,32,33,86,89,90,38,58,53,122,75,123,41,46],reset:[72,120,42,124,5,6,128],absent:20,optimizationbit:28,legalizeop:57,attornei:4
 3,inaccur:81,anew:115,absenc:[94,93],fco:66,llvm_gc_root_chain:82,emit:[],hotter:70,alongsid:124,wcover:101,request:[],noinlin:[109,36,124,68],xxxjitinfo:66,postscript:48,at_apple_property_sett:115,valuelist:46,function_entry_count:3,encrypt:43,stake:47,refactor:[19,71,33],instr0:50,instr1:50,instr2:50,entrypoint:[42,36],test:[],shrink:94,realiti:104,xxxtargetasminfo:66,fpreg:66,dw_op_addr:115,sync_command:[],"2acr96qjuqsym":43,sanitizercoverag:42,debugflag:[28,20],outdat:12,clang_cl:13,pathnam:[38,112],addtmp:[24,25,29,30,31,32,33,16,17,18,19,23],set_value_nam:[16,17,18,19,23],libgcc1:12,concept:[],mayload:8,consum:[],dw_tag_inlined_subroutin:115,supplement:[117,0],subcompon:43,value_typ:76,middl:[],zone:36,graph:[],certainli:[48,82,26,53,15,63],jvm:[26,15],terror:125,"0x200":115,dootherth:101,munger_struct:114,fom:48,brows:[29,72,119,23],seemingli:66,dw_apple_property_readonli:115,avx1:13,avx2:13,administr:[],aad8i8:94,gui:[96,101,72],libthread_db:109,adc64ri8:8,gut:[],sparcinstrf
 ormat:66,usescustominsert:8,upper:[36,101,20,66,41],isvolatil:36,brave:[111,22],bpf_jgt:94,preservemost:36,cost:[],build_fmul:23,bpf_jge:94,cov_flag:42,after_bb:[17,18,19],gr16:94,r_amdgpu_abs32:94,scaffold:[111,22],"23421e":36,constantarrai:20,uniform:[101,20],isoptim:[36,115],outliv:[48,42,36],setter:[36,34,20,115],va_list:36,image_sym_class_funct:121,psabi:117,mappingnorm:76,defici:[],caveat:25,floatingpointerror:20,gener:[],inputcont:76,satisfi:[100,58,53,33,13,43,104,4,19,36],pcre_fuzz:42,vice:[],isstor:94,devirtu:[123,36],precursor:43,plotter:[18,32],helper_cuda:[],mach_universal_binari:89,behav:[100,101,58,36,73,53,105,120,81,59,62,9],myvar:114,triag:94,regardless:[48,10,101,72,92,82,36,84,115,33,74,96,103,106,19,20],extra:[],stingi:20,stksizerecord:97,marker:[],emitt:[],regex:[105,28,7,51],prove:[48,58,50,51,61,63,36],"super":[94,99,66],naddit:28,subvers:[],live:[],suppos:[76,113,50,94,86,14,120,44,4,36],lgtm:[71,119],tlsv1_method:42,"0xl00000000000000004000900000000000":36,
 cxxabi:38,finit:[94,34,36],viewcfg:[20,31],geordi:56,shouldexpandatomiccmpxchginir:53,iffals:36,logarithm:[],graphic:[18,26,15,42,32],at_nam:115,canconstantfoldcallto:57,prepar:[],focu:[102,1,94,127,99,9],cat:[38,82,28,13,89,42],ctfe:47,can:[],cam:42,debug_symbol:74,boilerpl:[16,82,28,34,113],heart:[40,67],underestim:36,raw_fd_ostream:24,basemulticlasslist:46,chip:[66,11,94,12,52,13,87,90],spu:66,abort:[101,120,94,93,128,36,20],spl:8,occur:[48,101,0,40,2,3,55,4,36,10,106,107,7,13,81,94,20,64,24,112,114,82,111,84,86,87,103,71,92,120,47,73,43,97,22,124,41,118,46],multipl:[],image_sym_class_regist:121,ge_missing_sigjmp_buf:101,regioninfo:48,"0x80":[107,115],x86instrss:66,product:[102,82,59,47,94,32,104,86,43,111,36,50,18,46,70,22],multiplicand:36,southern:[117,39],uint:87,drastic:4,lto_codegen_compil:99,breakag:43,voidtyp:20,goal:[],copyphysreg:66,getcalledfunct:20,explicit:[100,101,0,102,50,26,36,9,11,108,15,40,16,17,18,19,20,24,25,113,114,82,28,31,32,33,86,35,38,71,39,94,53,122,43,44
 ],dllvm_dir:72,objectimag:85,asynchron:[36,53],ghc:[94,36],thread_loc:[40,94,36],approx:[14,11],arch_nam:89,approv:[43,119,104],graphviz:[48,20],brain:101,svnrevert:38,cold:[36,63,70],still:[],ieee:[14,87,36,63,107],dynam:[],mypass:[86,20],conjunct:[72,67,49,36,122,4,7,128],image_file_machine_wcemipsv2:121,precondit:[],yaml:[],window:[],addreg:94,curli:[13,36,101,20,128],val_success:36,llvm_doxygen_qhelpgenerator_path:72,has_asmprint:44,non:[],evok:36,recal:[76,50,29,30,31,16,23],halv:57,half:[],recap:88,now:[],nop:[36,35,97,40],discuss:[101,0,102,40,96,5,59,62,80,56,113,36,8,81,20,111,22,66,28,115,86,38,119,43,97],group_segment_align:39,build_sub:[16,17,18,19,23],drop:[36,101,43,20,119],reg1024:94,reg1025:94,reg1026:94,reg1027:94,image_scn_align_1024byt:121,dw_tag_vari:115,domain:[94,66,82,26,15,110,36,8],z8ifx:43,replac:[],arg2:[27,36,21],condmovfp:128,contrib:38,backport:12,reallyhidden:28,year:[101,8],operand:[],rl4:11,happen:[],rl6:11,rl1:11,rl3:11,rl2:11,shown:[51,2,105,96,36,
 8,80,113,11,18,20,66,83,28,115,32,88,69,42,76,122,123,97,127],accomplish:[48,113,82,27,43,20,21],"_e32":39,oldval:[24,25,31,32,33,36],rational:[],indirectstubsmgr:[5,6],ldrr:66,release_34:38,release_31:38,release_30:38,release_33:38,release_32:38,argu:101,argv:[80,11,28,115,109,14,81,90,5,93,42],quark:81,ldrd:53,mandelconverg:[18,32],argc:[80,11,28,115,109,14,5,36,42],card:[40,52],care:[101,102,51,26,104,4,36,62,58,7,8,14,15,19,20,66,33,86,38,42,94,53,45,128],xor16rr:94,couldn:[24,50,5,6,58],adc32rr:8,unwis:[36,107],printlabel:66,adc32ri:8,blind:94,subrang:36,yourself:[38,57,72,119,36,43,20,128],stringref:[],size:[],yypvr:127,silent:[43,36,128,58],caught:[120,47,101,36],yin:76,himitsu:38,checker:[34,114,73],cumul:94,friend:[108,36],r173931:34,nummeta:82,ariti:82,especi:[38,43,72,102,66,48,50,28,101,52,53,115,3,63,36,71,4,122,20,9,64],dw_tag_interface_typ:115,apple_nam:115,cpu0:65,cpu1:76,llvmtop:86,mostli:[25,71,66,38,50,28,26,31,53,15,48,17,94,115],amazingli:[17,31],quad:[40,36,66]
 ,than:[],png:[42,72],"0x432ff973cafa8000":36,elf64_rela:94,d02:123,xcore:[],"__atomic_load":53,spisd:66,exampl:[],copy_u:[],optimist:36,p0v4p0f_i32f:36,browser:[56,119],anywher:[127,102,50,111,33,13,99,63,36,120,19,7,8,22],getint32ti:101,cc_sparc32:66,tsan:[],bitcast:[],engin:[],mccodeemitt:[94,34],begin:[101,76,50,104,96,4,36,62,9,85,107,58,113,115,60,63,16,17,18,19,20,22,23,24,25,66,82,28,31,33,38,71,39,120,94,54,43,97,124,46],importantli:[17,43,101,31,58],numrecord:97,toplevel:[16,17,18,19,22,23],cstdlib:[24,111,29,30,31,32,33],"39dfd58417ef642307d90306e1c7e50aaec5a35c":[],getpointers:82,renam:[38,6,49,36,115,33,101,5,19,20],crossov:42,mri:94,"_p3":115,steadi:100,callinst:20,llvm_libdir_suffix:72,femul:36,add_reassoci:[16,17,18,19],image_file_bytes_reversed_lo:121,capston:42,fifth:[36,66,11],ground:102,discardvaluenam:47,onli:[],ratio:70,image_rel_i386_dir32nb:35,expr_prec:[16,17,18,19,22,23],llvm_enable_abi_breaking_check:20,loadlibraryperman:[5,6,59,62,9],endloop:[24,25,31,32,3
 3,19],overwritten:[97,94,36,120],llvminitializesparctargetinfo:66,cannot:[48,101,0,102,1,51,26,105,96,4,36,9,85,58,7,61,15,81,20,66,114,82,28,29,86,37,35,88,41,72,93,94,53,122,43,120],truli:[59,20],mrm6r:66,inttoptr:[],operandlist:128,seldom:50,intermitt:38,bio_new:42,object_addr:82,sutabl:115,gettypenam:20,servaddr:5,rrinst:128,terminatesessionid:5,dllvm_include_exampl:38,hierarchi:[],istreambuf_iter:11,"0x48c978":42,foo_test:13,concern:[114,82,40,43,44,36,62],"1svn":104,initialize_ag_pass:86,dityp:25,mrminitreg:66,printinstruct:[34,66],regcomp:42,between:[],"import":[],run_long_test:13,paramet:[],constantpoolsect:66,modulesethandlet:[5,6,59,62,9],clang_cpp:13,dosomethinginterestingwithmyapi:42,blame:[102,119],"__text":94,intregssubclass:66,dw_tag_subrange_typ:115,pertain:[120,43,115],maptag:76,inputfilenam:28,nearbi:[100,50],inconsist:[101,115,114],qualtyp:101,image_sym_type_struct:121,gr32:[94,8,128],prefix2:7,prefix1:7,dispatch:[120,111,97,36,22,20],hvx:[],mutate_depth:[],damag:
 [],caret:105,clarif:[117,43,101],harmless:48,invert:[13,36,63],shim:48,valuekind:101,invers:[48,36],fixabl:63,uglifi:[16,30],getentryblock:[24,25,20,33],derefer:[36,114,20,115,81],ircompil:9,normalformat:28,llvmremovefunctionattr:47,getjitinfo:[94,66],thischar:[24,25,27,111,29,30,31,32,33],infrastuctur:2,eip:8,global_context:[16,17,18,19,23],retcc_x86_32_c:66,fastemit:34,trick:[],initializenativetargetasmpars:[25,30,31,32,33,5],dw_at_artifici:115,functionaddress:100,metric:[86,42,70,104],henc:[38,46,28,97,36,99],uncov:42,bias:[],eras:[24,25,28,31,32,33,53,20,47,115],mfenc:53,ship:[38,82,26,53,109,15,125],bigblock:90,freetyp:42,develop:[],no_instal:[],proto:[24,25,19,111,29,30,31,32,33,16,17,5,6,18,22,23],"__nv_powf":11,sizeofimm:66,bpf_lsh:94,p0v16f32:36,epoch:[76,107],cindex:66,externalstorag:28,document:[],finish:[1,49,50,104,36,85,109,16,17,18,19,93,22,23,24,25,29,30,31,32,33,86,72,119,120,94,125,127],futhermor:[],closest:[25,36],someon:[57,101,0,102,82,26,127,43,15,63,94],remove
 branch:66,valuelistn:46,gridsizei:11,tradition:[94,58],pervas:[20,113],createstor:[24,25,33],emitglobaladdress:66,ccc:[36,124],comment:[],r_mips_hi16:[],bitmap:124,tpoff:40,touch:[48,101,0,36,115,86,20],idl:62,noat:47,tool_verbos:[],speed:[38,101,72,28,33,13,14,43,19,62,42],create_modul:[16,17,18,19,23],dllvm_link_llvm_dylib:[],startreceivingfunct:5,struct:[],bb0_29:11,bb0_28:11,getx86regnum:66,bb0_26:11,desktop:74,identif:[38,12,36],gettoknam:25,treatment:[82,66],versa:[],real:[101,0,66,11,7,28,58,115,32,42,36,27,18,20,8],imul16rmi8:94,frown:43,"0x82638293":115,read:[],cayman:117,amd:[],regfre:42,googletest:2,bangoper:46,threadsaf:82,benefit:[24,48,101,58,82,42,114,30,115,54,63,6,20,62,9,64],lex_numb:[16,17,18,19,21,22,23],output:[],downward:36,strcmp:42,debug_pubtyp:115,matur:[82,40,28,63],"__dwarf":115,journei:[19,33],nonzero:[124,128],viral:43,getregisterinfo:[94,66],extralib:[],blockidx:11,lto_codegen_set_debug_model:99,rauw:[50,71,20],raw_string_ostream:[5,6,59,62,9],tok_binar
 i:[24,25,32,33],sixth:66,objectbufferstream:85,asan:[54,42],flagprototyp:25,"throw":[],dw_tag_subprogram:115,comparison:[],sra:[46,128],central:[4,115,120],greatli:[40,63,115],underwai:47,shadowbyt:97,srl:[46,128],numbit:20,chop:115,degre:[126,53,63,1],intens:[20,63,1],dw_tag_subroutine_typ:115,sixkind:36,backup:75,processor:[24,38,72,66,1,82,117,28,94,115,34,88,90,36,8],valuecol:78,bodylist:46,op3val:66,llibnam:28,localaddress:36,xxxbegin:20,outloop:[24,25,31,32,33,19],yout:76,your:[],parsebinoprh:[24,25,111,29,30,31,32,33],verifyfunct:[24,25,29,30,31,32,33],loc:[25,98,115,66,40],log:[],opengl:[47,26,15,101],aren:[38,101,102,114,48,82,36,26,30,31,58,96,43,15,83,16,94,20,62],haskel:[20,26,15,36],start:[],lop:42,returnindex:68,lot:[48,101,76,51,26,52,111,59,8,83,57,113,36,108,15,81,16,18,19,20,21,22,23,25,66,114,82,27,28,29,30,115,32,33,86,68,38,93,47,94,74,43,125],stkmaprecord:[40,97],submiss:43,typeid2:123,typeid3:123,typeid1:123,satur:[18,32],llvm_cmake_dir:72,"default":[],inlni:8
 9,start_bb:[17,18,19],bucket:[20,115],visibil:9,v31:36,v32:11,llvmgetfunctionattr:47,loadabl:[],scanner:[27,21],decreas:[90,54],opnam:66,producess:[],value_1:44,prepend:[105,36,20,115,81],valid:[],release_19:38,release_18:38,release_17:38,ignor:[100,1,50,111,55,7,9,56,58,36,115,60,16,17,18,19,20,21,22,23,24,25,66,27,28,29,30,31,32,33,116,70,38,42,94,43,124,44,45],you:[],release_14:38,release_13:38,release_12:38,release_11:38,poor:[102,17,101,31,40],polar:76,lowerbound:36,registri:[],base_offset:40,bpf_st:94,cmake_minimum_requir:[72,81],binfmt:38,pool:[66,94,86,97,124,55],reduc:[],assert:[],adc64mr:8,value_n:44,skeleton:[],osx:107,messi:94,ssl3_read_byt:42,month:[56,104],correl:[82,36],"__cxa_end_catch":120,getglob:66,pandaboard:52,paramidx:124,getnullvalu:[24,25,31,32,33,20],myregisteralloc:86,cpufrequtil:52,sparcinstrinfo:66,articl:[48,38,50,31,33,17,19],sdisel:71,gcfunctionmetadata:[82,97],phielimin:94,"_rr":128,dllvm_external_project:72,datalayout:[],verb:101,mechan:[],veri:[48,1
 01,1,50,51,26,52,104,111,7,8,108,56,58,59,115,60,62,13,15,63,81,16,17,18,19,20,21,22,23,113,114,82,27,28,29,30,31,32,33,86,34,36,38,40,93,42,94,53,76,43,124,120,45,128,47,110],passmanagerbas:66,targetregisterdesc:[94,66],methodbodi:66,my_list_of_numb:81,eatomtypetag:115,emul:[57,101,20,94,63,90,36],lldb:[101,47,115,109,43,44],cosin:[36,66],customari:[28,43,36],dimens:36,unnorm:36,fixedt:115,preserveal:36,casual:43,kistanova:126,dofin:[],nand:36,fpformat:[8,128],isobjcclass:115,llvmlibspath:[],fp128:[50,36,124],"0x00000100":115,signextimm:94,endfunct:81,getanalysisusag:[],modular:[44,86,84,101,58],exeext:13,mclabel:94,strong:[50,108,53,43,63,36,40,7],modifi:[],divisor:[14,36],ahead:[],dform_1:94,t1_lib:42,noimplicitfloat:[36,124],amount:[48,101,102,40,54,36,8,57,59,108,50,16,94,20,21,82,27,28,84,30,86,87,90,93,42,73,95,34,97,120],sphinx_warnings_as_error:72,n1757:101,ask:[],famili:[102,39,40,26,115,15,36,20],sequencetrait:76,dangl:[17,20],"0x710":89,is64bitmod:66,isimmedi:66,getproto
 :[5,6],zorg:126,massag:101,swich:53,bash:[4,127],auxiliarydata:121,taken:[48,94,107,66,58,49,50,28,26,120,123,3,15,63,36,40,4,20,8,83],distfil:[],zork:128,vec:[36,20],build_arch:64,cbtw:94,valuetyp:[57,94,8,66],sn_map:50,regoffset:45,oblivi:88,targetcallingconv:66,"0b000111":66,x00:121,x86instrmmx:66,device_i:14,histori:[38,43,119],ninf:36,"0x40054d":89,device_x:14,reindent:101,templat:[],vectortyp:20,unreli:[42,58],parsabl:[40,122],phrase:[101,81],uncheck:20,anoth:[],llvm_enable_rtti:72,snippet:[82,43,20],reject:[],circuit:[18,32],rude:120,personlist:76,secondlastopc:66,unlink:[38,20],retcc_x86common:66,logerrorp:[24,25,111,29,30,31,32,33],"0x00003500":115,stabil:43,undergo:[48,36],machinepassregistri:86,basenamesourc:[],polit:[94,102],inline:[36,115],egg:51,help:[],mbbi:94,soon:[49,42,31,86,43,111,17,99,62,22],mrmdestreg:[8,66],ffp:14,held:[43,36,119,88],ffi:[108,72],foo4:[75,99],xdemangl:105,foo1:[75,99],foo2:[75,99],foo3:[75,99],dfpreg:66,overhead:[82,36,42,108,30,78,16,20],eato
 mtypecuoffset:115,tok_els:[24,25,31,32,33],perserv:36,mergebb:[24,25,31,32,33],systemz:[],finer:58,dil:8,cee:20,dexonsmith:115,sentenc:101,wideaddr:36,ninja:[38,72,42,12,52,125],gmon:[],libllvm:[74,38,72],stopper:49,addenda:117,x0c:121,iff:36,scalarevolut:[],fulli:[],radare2:42,dir2:42,dir1:42,unknownvalu:36,heavi:[40,20,62],succ_iter:20,llvm_build_tool:72,beyond:[118,114,20,94,63,120,45,127,36,8],todo:[48,57,49,94,12,86,34,110],ific:28,isunaryop:[24,25,32,33],ppcinstrinfo:57,safeti:[],robert:14,publish:[49,101,20],debuglevel:28,astnod:34,regexec:42,unreview:43,labf:28,ast:[],errorp:[],dw_tag_volatile_typ:[36,115],mystruct:114,pub:[42,115],mips64:47,reason:[101,0,50,111,4,59,9,57,58,36,115,12,13,63,81,16,17,19,20,21,22,23,25,113,114,82,27,28,29,30,31,33,86,34,38,72,40,120,42,94,95,53,43,44,127,128],base:[],put:[100,48,101,102,76,50,104,7,80,58,36,115,109,13,93,82,27,28,30,31,33,86,38,119,20,94,53,120,127],asi:66,targetopt:24,intermodular:[56,99],wglobal:101,asm:[],basi:[40,27,28,32,
 82,36,55,18,20,21],r_mips_pchi16:[],launch:[14,59,11],american:42,warpsiz:11,lifetim:[],assign:[],myawesomeproject:36,obviou:[48,43,58,50,111,26,30,53,32,93,34,15,101,88,16,97,18,94,36,108,115],ultrasparc3:66,islazi:66,isregist:94,placehold:120,default_branch_weight:3,uninterest:[27,21],implementor:[16,17,30,8,31],miss:[101,39,1,36,51,12,53,32,33,75,93,63,18,19,20,111,22],st6:8,st4:8,st5:8,nodetail:55,st7:8,st0:[8,66,128],st1:[94,88,8,66],st2:8,st3:8,scheme:[6,66,82,20,125,68,33,101,36,55,19,59,9],disagr:102,schema:[76,2,121,115,67],adher:[102,43,110,4,20,8],xxxgencodeemitt:66,make_error:20,libunwind:47,bidirect:20,adc32ri8:8,grep:[24,38,72,28,94,52,13,7,51],stl:[38,101,48,42,76,20,108],stm:36,symbolinfo:[5,6,59,62,9],do_something_with_t:100,rootmetadata:82,gpr:[45,94,36,47,128],str:[24,25,76,88,11,59,42,29,30,31,32,33,121,111,36,5,6,20,62,9,80],consumpt:[86,42,94],aliaseeti:36,toward:[56,72,36,43,20,70],grei:49,randomli:79,gofmt:101,llvmaddmoduleprovid:[],"null":[],dllvm_target_arc
 h:12,attrimpl:34,imagin:50,unintend:48,bz2:38,lib:[],lic:48,ourfunctionpass:20,lit:[],unintent:43,useless:[26,31,115,15,88,17],numfunct:[100,97],syncthread:[],mixtur:128,c_ctor_bas:7,maco:[38,108,20],alpha:[36,66],mach:[],isbarri:[8,128],changebyt:42,clear:[101,40,36,61,16,17,18,19,20,22,23,24,25,29,114,82,111,84,30,31,32,33,43,44],implicitdef:94,getter:[36,34,20,115],clean:[],usual:[101,50,51,26,54,55,7,62,9,57,113,58,36,13,15,20,25,66,114,82,83,28,84,115,86,35,38,71,72,119,93,42,94,95,53,75,43,124,127,99,128],v4f64:36,unari:[],"__clang__":14,unsimm:94,v16:11,v15:36,instrins:36,i32imm:[66,128],"3x4":36,get_instrinfo_named_op:66,getgloballist:20,operandti:94,paus:[82,62,58],coerc:50,delin:2,pretti:[48,50,51,4,16,17,18,19,21,22,23,114,27,111,29,30,31,32,33,86,68,89,42,45,127,46,128],setnam:[24,25,29,30,31,32,33,20],xec:121,lastopc:66,"0x00ff0000":94,suspect:84,darwin:[100,25,94,13,97,89,36],ymm:36,defaultdest:36,dinod:25,prolang:51,parenexpr:[24,25,111,29,30,31,32,33,16,17,18,19,22,2
 3],has_asmpars:44,nativ:[],same_cont:35,"133700e":[29,23],setdata:101,rejit:16,llvmlibdir:[],image_scn_lnk_oth:121,dw_macinfo_start_fil:36,kawahito:94,userspac:120,"__llvm_profile_name_bar":[],ctaid:11,seventeen:83,compute_pgm_rsrc1_sgpr:39,xword:66,close:[],"0x0b17c0de":124,whatsoev:36,dwarf:[],glue:[94,108],unoptim:[38,87],particip:[102,119,20,13,43,36],parse_unari:[18,19],pifft:51,won:[],isprefix:28,srcloc:36,emitint32:82,makeup:20,fpform:8,memalign:54,numer:[28,37],isol:[],lowercas:[16,30,66],numel:36,distinguish:[80,82,20,26,15,88,40,4,36],both:[],clang_attr_identifier_arg_list:34,delimit:[38,39,46,120,81,45,36],fancyaa:86,sty:8,forgotten:24,getnumvirtreg:94,isrematerializ:8,lexidentifi:57,block_par:[17,18,19],"__objc":36,jeff:4,byval:[94,36,124],header:[],instrsch:20,hasdelayslot:8,linux:[],test_corpu:[],forgiv:50,llvm_enable_thread:72,addfunctionast:[5,6],stamp:107,territori:38,empti:[101,40,2,54,36,13,81,50,17,20,111,22,23,25,66,82,83,28,29,31,115,89,72,120,42,76,43,46,128],
 destructor:[101,20,108,86,120,36],newcom:[110,19,8,33],sslverifi:38,newinst:20,addpassestoemitfil:[24,86],threaten:102,patleaf:66,lattner:[26,15],imag:[85,47,94,32,37,35,18,36],citizen:20,imac:1,coordin:[82,40,76,36],modrefv:128,imap:38,look:[],use_bind:[16,17,18,19],invit:[5,6,59,62],ramif:114,"while":[],match:[],machine_version_major:39,loos:8,loop:[],pack:[29,49,94,63,124,36,23],malloc:[56,82,42,26,86,54,15,20],pragmat:47,readi:[50,104,111,9,85,115,16,17,18,19,21,22,23,24,25,27,28,29,30,31,32,33,86,75,43],readm:[13,38,43,127],jpg:42,"__gcmap_":82,threadlocalquarantinesizekb:54,thesparctarget:66,hideaki:94,"0x00001203":115,quadrat:[94,87,20],targetlow:[],fedora:[38,47],grant:[50,43,9],tokinteg:46,belong:[50,28,54,123,36,120,20],llvm_site_config:[13,96],dest:[24,36],octal:[28,37,107,128],curloc:25,conflict:[38,128,36,111,94,13,43,16,17,18,19,20,8,23],"0b10":128,goodwil:43,ccif:66,optim:[],image_sym_class_type_definit:121,temporari:[48,71,0,76,36,51,2,13,101,94,20,108],"3gb":96,vreg
 :94,numarg:[25,97],sha1:42,"0x16677e0":109,older:[38,66,82,28,52,53,43,63,45],curr:21,mctargetstream:94,cmake_toolchain_fil:[38,72],pointtoconstantmemori:58,"__main":86,reclaim:[71,36],use_:20,llvalu:[16,17,18,19,23],weakest:[94,53],predetermin:58,violat:[101,0,102,114,82,36,31,43,17,20],safestack:[47,36],cout:[24,101,11,76,14,108],isunord:53,emissionkind:[36,115],afre:61,source_filenam:36,dw_ate_unsigned_char:36,undeclar:[29,36,23],tick:107,dictionary_fil:42,xe8:121,shortcut:[27,21,22],supersparc:66,"__apple_objc":115,unknownptr:36,gettargettripl:[6,59],codegener:73,gnueabihf:12,dw_macinfo_undef:36,intregsclass:66,mcsectionelf:94,xterm:101,nothidden:28,game:43,optimizationlist:28,atomic_cmpxchg:53,characterist:[57,66,20,94,121,36,59,62],isproto:124,like:[],outright:114,signal:[100,120,28,53,109,13,36,42],resolv:[0,102,2,5,6,59,62,9,85,36,8,81,16,17,20,23,29,30,31,86,94,43,99],"______________________________________":20,"32bit":24,popular:[38,94,81,52,58],bpf_alu:94,regionsforfile1:
 80,regionsforfile0:80,ptroff:94,some:[0,1,2,3,4,5,6,7,8,9,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26,27,111,29,30,31,32,33,34,38,39,40,42,43,44,46,47,48,96,49,50,51,52,54,56,57,58,59,61,62,63,66,68,71,72,73,74,76,78,36,81,82,83,86,87,88,93,94,95,53,97,99,100,101,102,104,105,107,108,110,28,113,114,115,119,120,37,124,125,127,128],urgent:43,"__llvm_faultmap":100,mnemonicalia:94,getfunctionlist:20,mem_address:94,uselistorder_bb:36,addpreserv:[],"__sync_fetch_and_umin_n":53,printinlineasm:66,pathsep:[13,2],n2930:101,slash:[36,107],castinst:20,bcanalyz:[],unreferenc:[36,81],cgi:42,originput:28,cgo:14,jit_serv:5,stem:20,"_ztii":36,movsx64rr8:94,curtok:[24,25,111,29,30,31,32,33],disttarbz2:[],subtract:[80,57,94,36],"0x800":115,faith:120,blocksizei:11,idx:[24,25,101,114,83,29,30,31,32,33,36],nnnnnn:94,inaccessiblememonli:36,shini:86,blocksizez:11,f31:[36,66],blocksizex:11,block:[],"123kkk":28,gcroot:[],aq2:36,within:[48,101,0,102,76,50,51,2,54,7,9,94,11,36,115,14,81,16,17,18,19,20,64,24,25
 ,113,114,82,27,84,30,31,32,33,86,88,38,71,40,93,58,123,97,124,120,128],loadsdnod:20,proj_install_root:64,ensur:[100,48,101,102,1,40,104,55,36,94,11,7,108,13,63,19,20,23,25,112,66,82,28,84,115,32,33,86,35,38,120,58,53,43,97,124],llvm_package_vers:72,amaz:[18,32],properli:[],cmp32ri8:94,loopunswith:63,use_count:42,pwd:[38,42,12],bio_s_mem:42,vfprintf:36,newer:[38,96,43,53,109],cmpxchg:[],flagsfeatureb:76,flagsfeaturec:76,flagsfeaturea:76,specialti:20,info:[],inreg:[94,36,124,66],"0xc3":128,"__bitcod":124,hipe:[94,36],abs_fp64:8,similar:[48,101,1,50,52,4,7,62,83,107,11,36,13,14,81,16,17,18,20,21,64,23,25,112,66,114,82,27,28,29,30,31,32,86,34,35,38,120,42,94,53,76,43,124,128],createdefaultmypass:86,obviat:64,reflectparam:11,doesn:[],repres:[],arg_iter:[20,33],incomplet:[101,108,5,6,59,62],nextvari:[31,32],minsiz:36,titl:[43,119],speccpu2006:51,nan:[90,87,36,115],compileondemandlay:[5,6,59],proxi:94,setenv:[],"0x00007fff":94,resign:43,xtemp:53,drag:119,canfoldasload:8,rnnnn:43,svn:[],typ
 eid:[],infrequ:86,svg:72,addmbb:94,orbit:[18,32],devminor:11,depth:[48,50,47,94,31,8,75,36,17,62,28],loadobject:85,unconnect:114,mystringtyp:76,msbuild:[96,72],thetargetmachin:24,getkind:[34,113],deletesizemismatch:54,image_scn_mem_preload:121,compact:[25,94,82,120,47,26,15,55,97,20],friendli:[43,101,102],"__llvm_profile_name_foo":[],breakcriticaledg:86,aris:[36,43,20,114],instr_iter:94,yoyodyn:43,findstub:[5,6],then_bb:[17,18,19],image_sym_dtype_arrai:121,runnabl:38,nonatom:115,llvmdisasminstruct:45,weakvh:20,gender:102,button:119,llvm_enable_doxygen:[38,72],use_llvm_target:[16,17,18,19],dw_tag_const_typ:[36,115],ccifnest:66,amdgpu_hsa_kernel:39,lazier:[62,9],relink:[112,93],vgpr:36,calleef:[24,25,29,30,31,32,33],jump:[],ult:[31,33,16,17,18,19,36,23],download:[72,66,49,47,12,96,104,13,75,14,126,20],click:[96,119],hasoneus:101,poke:124,slight:35,espresso:51,cell:66,experiment:[],registerschedul:86,ramsei:94,init_v:19,legalizeact:66,becom:[48,101,1,52,36,62,113,8,13,63,81,17,19,20,11
 1,22,66,114,28,31,33,86,88,94,97],accessor:[86,111,94,115],"_source_dir":72,startexpr:[24,25,31,32,33,19],convert:[],convers:[],vacat:0,value_kind:36,converg:[18,36,32],solaris2:86,findings_dir:42,chang:[],hexagon:[],epilogu:[82,36,66],chanc:[3,85,27,76,21,43,63,36,8],testcase_dir:42,selectinst:101,n3272:101,although:[101,40,2,96,36,57,13,14,81,20,23,113,67,82,83,28,32,86,38,42,94,53,43,124,44,127],danger:[7,0,36,20],revok:43,win:[101,20,58],degen:36,dyn_cast:[],"boolean":[],llvmtyperef:57,"0x0000000000d953b3":109,basic_block:23,externallyiniti:36,getrawsubclassoptionaldata:50,implic:[94,43],recordid:124,fibi:[19,33],remaind:[80,38,57,66,94,13,44,36],llvm_enable_warn:72,createfsub:[24,25,29,30,31,32,33],gc_transition_start:40,numelt:124,benchmark:[38,1,49,51,115,13,14,43,20,64],landingpad:[],dcmake_osx_architectur:38,nvptx:[],findlead:20,callvoidvoid:5,retriev:[85,107,119,11,40,28,76,86,97,120,20,42],image_scn_gprel:121,perceiv:[26,15],memory_order_acq_rel:[36,53],linearscan:[86,90,
 94],jitsymbol:[5,6,59,62,9],meet:[38,0,102,50,94,86,43],machine_kind:39,control:[],malform:[48,20,93],sudo:[38,51,52],typeprint:57,llvm_use_intel_jitev:72,myfooflag:76,int_get_dynamic_area_offset:36,sought:36,emitepilogu:66,clang_attr_arg_context_list:34,egrep:38,addpreemitpass:66,dissolv:[],tag_base_typ:115,templatearglist:46,lto_module_is_object_fil:99,live_s:82,eliminatecallframepseudoinstr:[47,66],mydoclist:76,"0x3feaed548f090ce":30,filterclass:78,syscal:94,image_scn_lnk_info:121,vsetq_lane_s32:88,subtyp:[120,66],primaryexpr:[111,22],llvmgetdatalayoutstr:47,irtest:72,jne:94,onzero:36,newptr2:36,objectlay:[5,6,59,62,9],distzip:[],outer:[24,25,101,61,76,31,33,86,120,17,19,36],consensu:43,sextload:[8,66],topdistdir:[],attrparserstringswitch:34,build_alloca:19,exact_artifact_path:42,handl:[],auto:[],handi:[127,29,20,62,23],ctor:[101,36,61,108],memberlist:66,armgenregisterinfo:34,p15:11,p16:11,p17:11,front:[],p19:11,"enum":[101,76,78,36,8,57,113,58,115,20,111,24,25,66,82,27,28,29,30,
 31,32,33,34,68,47,94,121,118],modr:94,somewher:[86,113,36,51,29,32,13,120,18,7,23],faultkind:100,slide:[14,20,102],ourfpm:[25,33],cs2:[36,58],upward:[2,36],unwind:[48,71,66,36,47,94,61,35,63,120,69,59],globl:[40,35,39,11],selectiondag:[],grok:[29,108,23],chunk:[48,101,88,42,94,124],exctypen:120,special:[],image_sym_type_byt:121,"0x00000130":115,influenc:[86,71,36,115,88],discharg:63,suitabl:[80,48,11,82,36,28,94,85,13,105,14,124,81,20],hardwar:[],statist:[],llvmtransformutil:64,spec95:51,lcssa:[],"__cuda_ftz":11,manipul:[],undo:88,typebuild:[57,20],getpointertonamedfunct:85,ecx:[94,35,8,128],image_scn_mem_writ:121,bodyexpr:[24,25,31,32,33,19],bclinklib:[],mac:[38,107,109,86,104,20],keep:[],counterpart:36,bpf_and:94,use_empti:20,dumpmymapdoc:76,svptr:36,linkallcodegencompon:86,qualiti:[],fmul:[],prng:42,stump:66,find_a:20,atomic_f:53,rs1:66,has_disassembl:44,scalartrait:76,perfectli:[101,114,7,111,94,36,108,22],mkdir:[38,72,42,75,14,51],second_end:36,attach:[38,101,109,119,11,123,36,
 115,29,30,31,32,33,43,19,20],attack:102,functionpassctor:86,createparametervari:25,"final":[],prone:[28,94,8,52],my_valu:101,rsi:[94,8],fuzzi:42,methodolog:120,proactiv:[43,93],rst:[94,34,127],exactli:[],rsp:[40,94,95,8,97],rss:42,ehashfunctiondjb:115,bloat:101,claim:53,instvisitor:[57,20],"0x00001000":115,dubiou:107,dumb:[26,15],f16:36,exhibit:[93,53],multhread:20,xor8rr:94,reg2:7,procnoitin:8,reg1:7,goldberg:82,lightli:[49,36],tabl:[],need:[],altivec:[94,36],mangl:[101,37,115,43,5,6,36,9],createfunctiontyp:25,ind1:36,reloc_pcrel_word:66,"0x04":115,"0x05":97,"0x06":97,"0x07":97,"0x00":[80,97,107],parse_extern:[16,17,18,19,22,23],"0x02":[80,115],fileit:28,unawar:36,lgkcmt:39,platformstripopt:[],llvmgold:75,detector:50,equal_rang:20,singl:[],parseidentifierexpr:[24,25,111,29,30,31,32,33],discop:25,discov:[94,82,42,2,31,33,104,17,4,19,115],rigor:94,x86_ssecal:66,deploi:119,x86_fp80:[50,36,124],sub_8bit:83,url:[43,119,127],hasrex_wprefix:8,"0xe8":128,indx:76,inde:42,llvm_parallel_link_
 job:72,libcmt:96,"0x0d":97,"0x0e":97,constrain:[38,108,120,29,74,13,128,36,23],disable_assert:[74,104],"0x0a":[97,107],"0x0b":97,"0x0c":80,ssl_load_error_str:42,cute:[26,15],verbos:[41,2,107,92,76],objc:[56,127,115],config_fil:[],molest:36,anywai:[48,101,12,36],varnam:[24,25,31,32,33,17,19],tire:[],losslessli:50,bpf_alu64:94,envp:109,x86_thiscal:94,themodul:[24,25,29,30,31,32,33],add_to_library_group:44,llvmtypekind:57,getprevnod:[],q31:36,tbb:66,shr:101,enabl:[],getmbb:66,she:[126,8],contain:[],shapekind:113,grab:[25,49,104,34,17,18,19,20],image_file_local_syms_strip:121,shl:[],legaci:[24,72,36,30,31,32,33,5,6,59,62,9],pni8:120,singlton:[5,6,59,62,9],nolink:28,rc1:49,vectorize_width:1,target_link_librari:72,image_scn_mem_16bit:121,mileston:50,statu:[],correctli:[101,50,36,108,13,40,17,94,20,111,64,114,28,31,115,86,72,120,76,95,53,43,22],writter:28,sectvalu:28,realign:36,written:[],cxx_flag:52,neither:[48,124,58,50,42,96,97,63,88,120,36,47],tent:36,bleed:[56,81],vfp3:12,dagschedul:[
 ],kei:[],header_data_len:115,parseabl:[40,36],crc32:54,setgraphcolor:20,monitor:58,islandingpad:83,xxxreloc:66,admin:126,handledefinit:[24,25,111,29,30,31,32,33],behaviour:[],dw_tag_inherit:36,test_format:2,unglamor:43,outfil:79,multi_v:28,orig:36,quit:[40,26,4,59,56,57,58,36,109,15,63,50,17,20,23,114,82,29,31,38,94,97,127],slowli:[38,43],addition:[38,94,48,82,36,28,58,53,75,43,40,44,20],setindexedloadact:66,libdir:112,image_sym_dtype_nul:121,treat:[],isdopcod:[57,94],seqeuenc:47,cputyp:124,alphacompilationcallback:66,otp:36,createcal:[24,25,29,30,31,32,33,20],acq_rel:[36,53],replic:[73,99,128,76],main:[],dw_tag_typedef:[36,115],harder:[48,40,42,108,4,36,111,22],qualcomm:47,print_str:[16,17,18,19,22,23],engag:43,demo:[],rootstackoffset:82,povray31:51,revis:[38,101,72,119,115,104,43,97,63,20],insertdeclar:25,so_reuseaddr:5,welcom:[102,50,26,96,5,6,59,62,9,117,15,16,17,18,19,21,22,23,24,25,27,111,29,30,31,32,33,86,38,42,43],parti:[101,0,40,43,63,64],reloc_picrel_word:66,print_float:[1
 6,17,18,19],ro_signed_pat:8,llvm_all_target:[38,66],setcategori:28,matcher:[94,42,34,118],nightli:[],http:[38,65,101,117,119,56,49,42,12,96,104,13,14,43,116,126,51],hsatext:39,tokprec:[24,25,111,29,30,31,32,33],effect:[],isopt:28,llvm_use_oprofil:72,global_s:20,bitpack:13,appendinglinkag:20,dllvm_enable_p:12,protector:[36,115],dw_form_strp:[7,115],well:[],makefileconfig:[],optsiz:[47,36,124],undefin:[],llvmgetbitcodemoduleprovid:[],memory_order_consum:53,createindirectstubsmanag:5,mistaken:[16,30],diflagartifici:36,aform_1:94,aform_2:94,namedvar:25,xs1:117,size1:36,size2:36,size3:36,outstream:82,dcmake_build_typ:[38,42,52],densiti:[18,101,47,32],logger:0,warrant:57,nodebuginfo:28,takelast:20,bpf_xadd:94,howto:[65,34,12,127],mcsectioncoff:94,add_gvn:[16,17,18,19],burden:[43,36],getopt:28,n2343:101,lbar:94,n2346:101,n2347:101,loss:[82,20],lost:[36,26,15,108,120],"0f3fb8aa3b":11,ldflag:[24,25,112,29,30,31,32,33,5,6,59,62,9],necessari:[101,40,104,105,54,4,7,80,57,107,58,36,12,109,13,123
 ,63,94,20,24,25,66,82,28,29,85,86,88,68,70,38,71,72,119,120,73,53,43,97,127,99],rotl:57,martin:[],profraw:[80,105,125],page:[],"100mb":[],didn:[101,94,50,29,115,33,86,63,36,19,20,22,23],revert:[38,43],"04e":36,mistyp:101,notfp:128,repeat:[48,49,36,115,120,50,45,93],home:[38,51,52,109,13,63,20],librari:[],hannob:42,win32:[13,4,96,94,38],setmcjitmemorymanag:85,broad:[82,27,28,30,16,20,21],createexpress:25,overlap:[94,58,1,61,86,97,81,36],estim:[50,70,1],exitonerror:5,combinedalloc:54,asmstr:[8,66,128],myfunct:11,encourag:[48,73,102,38,26,101,43,15,20],ifequ:36,nutshel:20,offset:[],pi8:123,image_file_32bit_machin:121,testsuit:7,bcreader:112,freedom:[36,20],viewvc:56,bodyitem:46,cocoa:36,cmake_cxx_flag:72,attrtemplateinstanti:34,pointless:[40,120],"0x00000110":115,whom:50,gcov_prefix:105,image_file_removable_run_from_swap:121,"_cuda_ftz":11,downgrad:[],dbuild_shared_lib:38,ndebug:[74,28,72],nuw:[36,63],global_iter:20,interleave_count:1,pty2:36,as_float:[16,17,18,19],liveintervalanalysi:
 94,eax:[66,83,94,35,36,7,8,128],gain:[],spuriou:[101,36],overflow:[],highest:[24,25,111,29,30,31,32,33,88,16,17,18,19,36,22,23],eat:[24,25,27,28,29,30,31,32,33,111,16,17,18,19,21,22,23],liblto:[],dmb:53,displac:[94,36],displai:[80,48,101,66,51,69,27,28,2,122,126,105,43,81,37,55,113,45,94,21,102],sectiondata:121,w31:36,w30:36,cruel:127,"0xffbef174":86,indefinit:42,llvm_enable_assert:[72,20],add_llvm_loadable_modul:72,bpf_op:94,unconditionali:[],atyp:114,isconvertibletothreeaddress:8,reciproc:36,lastchar:[24,25,27,111,29,30,31,32,33],twist:9,intregsregclassid:66,fourinarow:51,dumpabl:86,quot:[72,39,83,28,76,115,13,44,36,42,128],acloc:[],dloc:7,tok_var:[24,25,33],arctan:76,hash_set:20,getjmp_buftyp:101,futur:[],rememb:[101,102,40,51,52,96,36,9,108,12,17,19,20,111,22,24,25,114,28,31,33,86,38,42,43],parse_id:[16,17,18,19,22,23],tmp2:[19,33],stat:[],cmake_build_typ:[38,72,81],dw_tag:115,stab:115,same_s:35,dyld:85,sphinx:[],samsung:47,twoaddressinstructionpass:94,indirectli:[101,36,53,128]
 ,bcc:66,portion:[80,38,41,66,48,120,83,28,94,30,93,43,81,16,45,36],image_file_machine_sh3dsp:121,"7ykb2k5f":116,callingconv:[],getpointertofunct:[85,25,20],tcpchannel:5,enable_sgpr_kernarg_segment_ptr:39,secondli:25,whose:[80,101,124,66,58,37,46,42,94,93,32,33,128,43,36,18,19,20,111,22,115],accur:[],unaryexprast:[24,25,32,33],parse_var_nam:19,"0x20":115,sanitizercoveragetracedataflow:42,swap:[36,52,88,53],getllvmcontext:101,preprocess:[73,108],aux:20,doubleword:36,downstream:[60,70],"void":[],llbuilder:19,build_stor:19,affect:[102,49,50,104,4,36,11,7,12,14,17,20,28,30,31,86,88,72,73,53,46,128],x86_stdcallcc:124,mybranch:38,theier:48,bpf_x:94,stageselectioncat:28,image_file_machine_m32r:121,bpf_w:94,uint32:[100,97],scalarbitsettrait:76,vector:[],bpf_h:94,bpf_k:94,llvm_build_test:72,"0x2a":88,initialis:[24,28,8],bpf_b:94,whirlwind:[111,22],likeli:3,cpu_x86:76,"10m":42,"__cuda__":14,"10x":14,aggreg:[],binop_preced:[16,17,18,19,22,23],bpf_imm:94,dw_apple_property_unsafe_unretain:115,eve
 n:[100,101,102,1,50,51,26,52,4,5,7,8,107,58,36,62,13,14,15,63,40,16,18,19,20,21,2,113,82,27,110,30,31,32,33,86,34,90,70,38,119,42,94,76,37,124,45,127,99,128],rope:20,fcur:50,addllvm:[72,81],neg:[],s_endpgm:39,transcrib:[29,23],nex:[],libpo:28,net:[100,56,126],add_depend:81,metadata:[],llvmgetattribut:47,elimin:[],centric:36,old_bind:19,never:[100,48,101,76,50,51,26,105,36,80,107,58,113,108,14,15,16,20,66,114,82,86,88,47,94,53,75,99],restat:101,q15:36,met:[82,50,54,94,36],ccassigntostack:66,image_scn_cnt_initialized_data:121,interpret:[40,26,36,8,80,41,115,60,13,15,16,17,18,19,20,111,22,23,24,25,112,2,28,29,30,31,32,33,88,90,38,72,94,122,74,97,124,44,46],dcmake_crosscompil:12,gcname:124,credit:43,harass:102,permit:[24,25,71,82,36,94,33,13,87,35,19,20,128],parlanc:[27,123,21],volunt:[49,126,42],immin:104,bpf_jset:94,avenu:0,machineregisterinfo:94,quickcheck:20,fcoverag:[80,105],handlerpcoffset:100,leaki:42,createnvvmreflectpass:11,icc_n:66,disambigu:[63,58],calm:[19,33],recommend:[101
 ,40,2,96,36,11,61,13,63,81,16,19,22,24,114,82,111,30,33,86,38,72,119,42,94,74,43,47],icc_g:66,type:[],tell:[],esi:[83,94,8],"__eh_fram":94,columnend:80,warn:[],all_build:96,wari:63,align_nod:36,dw_tag_apple_properti:115,room:[86,111,22,68],rightr:50,x8b:121,dw_apple_property_nonatom:115,setup:[],thefunct:[24,25,29,30,31,32,33],librarygroup:44,root:[],clang_cc1:[13,7],defer:[85,50,30,16,59,62,9],give:[],dlsym:[16,86,30],dw_at_loc:7,binpath:109,subtmp5:[19,33],force_on:72,dragonegg:[56,43,94,104],unsign:[101,1,50,3,36,80,11,115,94,20,23,24,25,66,114,82,83,28,29,30,31,32,33,34,58,76,124,99],secidx:35,symaddr:[5,6,59,62,9],sata:52,tbaa:[],dependfil:[],answer:[48,101,113,56,50,28,58,30,31,33,63,127,16,17,114,19,36,62,108],registerlist:66,config:[],confid:43,reloc_absolute_word:66,attempt:[48,101,0,40,4,5,6,36,62,20,85,58,41,63,93,66,84,86,38,120,94,43,97,124],third:[101,50,51,26,104,36,80,15,40,94,20,64,23,25,66,114,82,28,29,115,86,38,120,76,43,97,124,125],"0x7fffe3e85ca8":42,maintain:[5
 7,101,124,58,82,50,28,94,53,104,86,54,43,97,36,81,4,20,8,115],yourregex:7,vfp:[36,88],decl:[29,8,113],"0fbf317200":11,privileg:[4,36,9],gcda:105,invalidid:5,"_except_handler3":120,sigplan:[82,94],"_except_handler4":120,better:[48,101,1,50,51,26,52,36,62,9,94,7,109,15,17,19,20,22,111,31,33,86,71,120,42,73,53,43],argti:36,persist:[42,20,102,81],vmcnt:39,gpucc:14,ircompilelay:[5,6,59,62,9],newtoset:101,dummytargetmachin:66,promin:[13,51],overestim:36,promis:43,runtimedyldmacho:85,usertarget:[],coveragemappingdataforfunctionrecord0:80,mapsectionaddress:85,isel:[94,71,128,66,118],"instanceof":20,grammat:[51,111,22],grammar:[57,111,32,81,18,22],meat:16,weng:14,setdescript:28,getvalu:[101,20],somefancyaa:86,went:[17,30,31],thenv:[24,25,31,32,33],side:[48,101,11,82,50,111,29,58,31,32,53,13,36,40,17,18,94,20,22,23],bone:[97,66,9],mean:[48,101,0,102,76,50,26,104,54,4,7,8,9,107,58,113,36,115,12,61,62,13,15,63,81,16,17,120,19,20,21,64,23,25,2,66,114,82,27,28,29,30,31,33,86,37,35,88,38,72,119,39
 ,40,99,42,94,122,75,43,124,83,128,46,110],rev64:88,awri:[],add_ri:128,taught:94,f108:11,f107:11,collector:[],getsextvalu:20,unbound:[94,36,66],crucial:[36,119],bpf_end:94,content:[],rewrit:[48,101,113,66,40,33,71,19,36],mtripl:[36,87,7,90],rare:[100,101,124,102,66,82,20,94,12,63,36,120,7,62,128],dfpregsregclass:66,reader:[],die_offset_bas:115,end_cond:[17,18,19],parseforexpr:[24,25,31,32,33],nodetyp:66,linear:[38,114,58,94,86,87,90,20],parse_definit:[16,17,18,19,22,23],current_corpus_dir:42,wherea:[20,47,94,14,63,88,120,36],isv9:66,situat:[86,48,0,113,66,1,59,28,94,30,53,13,75,120,36,50,16,114,20],infin:36,ineffici:[1,94,33,63,124,19,20],f89:11,getfunctiontyp:20,retcc_x86_32_fast:66,dw_at_rang:115,nummodulevalu:124,typesaf:36,ish:[18,32],isn:[],ism:5,isa:[],getinstrinfo:[94,66],isd:[57,94,53,66],cpuinfo:52,symbollookup:5,floorf:1,my_kernel:11,thereof:102,targetregistri:[24,94,66],hook:[120,94,31,17,93,64],unlik:[48,101,40,52,59,36,81,16,19,20,113,82,30,33,86,38,120,94,53,75,43,97,12
 4,46],featureb:76,featurec:76,featurea:76,massiv:[42,34,60],payload:[94,36],hood:[13,80],global_empti:20,tsc701:66,acquaint:9,sevenkind:36,pane:119,ieee754:36,sometim:[38,114,43,124,113,66,48,7,28,94,101,93,13,14,34,111,36,50,76,20,42],sphinx_output_html:72,arm_apcscc:124,memcmp:42,dwell:29,filepo:28,llvm_enable_pedant:72,bodyv:[24,25,33],a32:88,namespac:[],build_cond_br:[17,18,19],somewhat:[56,101,58,36,51,53,32,43,40,18,20,111,22],buildmod:13,dllvm_tablegen:12,bitpattern:36,ri_inst:128,symptom:38,nail:[17,31],r14d:8,silli:[27,108,101,21,58],llvm_link_llvm_dylib:72,keyword:[],mcdesc:66,r14w:8,matter:[57,101,53,86,43,97,16,36],nakatani:94,modern:[],mind:[101,111,33,43,19,20,22],stackar:82,bitfield:53,seed:[42,79],seen:[101,124,66,40,59,28,26,30,32,122,86,15,36,50,18,94,20,47],seem:[94,72,113,58,82,50,28,60,88,114,93,9],seek:[48,43,35,114,56],minu:[95,36],ty2:36,memcheck:[13,2],image_sym_class_register_param:121,rethrow:[40,120],myset:101,myseq:76,distsourc:[],cudevic:11,regular:[38,
 10,101,107,51,76,50,28,26,53,116,105,15,36,83,7,42],ccassigntoreg:66,secrel32:35,tradit:[48,38,27,94,115,86,37,125,20,21,9],simplic:[82,27,29,97,20,23],don:[],pointe:[36,124],simplif:[86,48,93],doc:[],obtus:114,dog:28,expandinlineasm:66,digress:[18,32],isatleastorstrongerthan:53,my_kei:101,dot:[],"0xffff000000000002":97,hunger:[26,15],visitor:[57,82,27,29,34,93,21],esoter:128,llvm_enable_werror:72,syntax:[],selftl:42,ehabi:47,image_sym_class_weak_extern:121,istruncatingstor:66,despit:[40,28,94,53,115,86,110,36,8,128],explain:[56,101,72,107,119,58,50,94,95,33,86,88,27,19,20,21,108],sugar:36,regnum:97,folder:[38,72,36],accumulateconstantoffset:50,pinst:20,hasgc:50,stop:[38,57,101,72,102,82,36,42,60,120,86,43,83,20,111,22],llvm_enable_lto:72,bar:[101,1,40,2,122,36,80,11,7,108,61,13,81,17,20,23,28,29,31,115,35,72,94,76,123,46],"__atomic_compare_exchang":53,sacrific:[50,36],bpf_div:94,baz:[101,1,20,28,31,115,123,81,17,122,46],reload:[24,25,71,82,42,94,33,19],bad:[25,101,49,50,76,115,32,9
 3,36,41,4,18,20],memorysanit:[42,36],ban:0,shtest:2,addinstselector:66,flagpointi:76,cstdio:[24,25,111,29,30,31,32,33],instalias:94,datatyp:[27,28,94,20,21],"0x42":124,"0x43":124,v8f64:36,msan:42,subject:[101,119,76,94,43,20],p1i8:[40,11],said:[101,36,26,115,54,15,120,20],myinitprng:42,double_typ:[16,17,18,19,23],ld64:47,simplest:[94,66,76,28,29,62,96,111,125,16,42,22],attribut:[],add_memory_to_register_promot:19,triplet:[28,36],howtousejit:112,manpag:81,lazi:[],irmov:[],diflagprototyp:[36,115],abs_fp80:8,configurescript:[],add_custom_command:81,imagmag:[18,32],against:[48,102,51,54,3,7,107,11,36,108,61,13,123,63,20,112,113,29,38,72,120,42,76,74,43,125],fno:[42,1],uni:11,readnon:[48,11,40,115,123,63,124,36],constantindex:97,uno:36,foobaz:101,createload:[24,25,33],devbufferc:11,devbufferb:11,devbuffera:11,foobar:[101,76],int32_t:[82,76],rcmemorymanag:5,"16b":88,loader:38,parse_var_init:19,"__________________________________________________________":20,three:[48,49,50,51,7,36,108,13,8
 1,93,111,22,66,114,83,28,31,86,34,38,41,40,20,94,122,120,124,125],objc_properti:115,specul:[58,120,53,14,63,36],succ_begin:20,trigger:[85,10,101,72,58,82,36,42,73,30,62,13,93,97,83,76,59,51],interest:[48,101,76,40,51,26,77,96,111,55,7,62,9,85,56,58,36,115,108,13,15,63,16,17,18,19,20,21,22,23,25,2,113,82,27,28,29,30,31,32,33,86,88,38,120,42,94,53,43,41,126,47],basic:[],tini:[50,113],llvmpassnam:72,build_load:19,suppress:[82,36,2,101,76],mce:66,multithread:[],lpae:53,lpad:[120,36],argumentexpr:[16,17,18,19,22,23],getsubtargetimpl:[82,66],llvm_include_test:72,terminatorinst:[101,3,20],ugli:[18,108,7,32],subsequ:[85,48,114,94,66,1,120,28,29,30,115,97,5,6,36,45,128],intregsvt:66,itinerari:[94,8,66],noredzon:[36,124],slt:36,servic:[4,108,58],lex_id:[16,17,18,19,21,22,23],slp:[],splitdebugfilenam:36,calcul:[86,48,71,66,58,36,51,94,31,115,13,17,114,20,70],neat:62,typeflag:115,occas:101,sle:36,spawn:[],r600:[94,39],gninja:42,xxxkind:113,disappear:[38,108,52],grown:[18,26,15,32],receiv:[85,0,
 124,59,42,94,120,63,36,81,20,8,22],make:[],bitmask:36,who:[101,0,50,26,4,36,9,80,56,13,14,15,81,19,66,33,38,119,73,74,43,44],isspac:[24,25,27,42,29,30,31,32,33,111],setcompileact:[5,6],kevin:94,"0x5cf8c24cdb18bdac":80,"__emutls_get_address":[],ssl_ctx_new:42,zlib1g:[13,12],kib:28,overs:20,revector:[48,20],binopprototyp:[18,19],vehiclemak:101,isaddresstaken:83,ea_r:94,addrawvalu:68,inherit:[86,101,113,58,20,28,94,123,74,34,4,46,8,128],llvm_dir:[50,72],endif:[80,25,101,28,26,62,14,15,81,4,5,6,59,42,9],programm:[],paradigm:[47,20,114],left:[48,101,1,50,51,36,8,9,107,63,81,17,94,93,22,23,25,66,111,29,31,76,43,124],projusedlib:[],identifi:[],op1:[36,124],just:[48,101,88,76,49,50,51,2,52,105,96,111,55,4,5,6,7,8,9,108,80,94,58,113,59,115,60,12,62,13,15,81,16,17,18,19,20,21,22,23,24,25,26,66,114,27,28,29,30,31,32,33,86,34,35,36,90,37,70,125,107,38,119,40,93,73,95,53,75,43,97,64,124,83,44,127,128],op3:66,bandwidth:36,human:[103,38,101,106,102,92,48,50,76,122,86,105,55,89,98,36,8,83],nowadai:
 12,yet:[48,101,50,51,5,6,59,62,9,85,36,61,14,40,16,17,18,20,112,66,82,83,28,29,31,32,86,126,120,47,94,53,122,44,42],languag:[],awaken:120,character:36,uint16:[100,97],save:[94,1,96,55,59,85,57,11,36,115,61,16,17,18,19,20,24,25,66,28,30,31,32,33,88,38,72,119,120,47,73,74,97,124,42,128],vpsubusw:13,opt:[],applic:[100,101,50,51,26,105,36,8,85,56,117,107,13,15,63,40,16,18,20,21,112,66,82,27,28,30,32,86,88,72,120,42,94,43,97,124,44,128],segnam:28,"0x0000000000dc8872":109,opc:[24,25,128,32,33],wojciech:48,fact1:50,fact0:50,getinstlist:20,negat:[18,94,36,124,32],dindex:66,llvmcreatesimplemcjitmemorymanag:97,machinepassregistrynod:86,funcion:[],unnecessari:[],cxxflag:[24,25,112,29,30,31,32,33,5,6,59,62,9],www:[42,104],deal:[100,48,101,124,102,113,120,115,53,33,34,43,88,19,20,62],maxim:[27,42,21,124,90],dead:[],intern:[],hd6xxx:94,interg:[],make_pair:[24,25,50,33],norman:94,insensit:58,xmm11:8,tracker:[43,102,119],hasopsizeprefix:8,getchar:[24,25,27,111,29,30,31,32,33],hatsiz:76,creatur:[27,
 18,21,32],burg:71,idiomat:[13,101,20],bold:127,identifierexpr:[24,25,111,29,30,31,32,33,16,17,18,19,22,23],uncompress:[38,20,72],burn:52,buri:101,strippointercast:101,promot:[],burr:90,codenam:47,nothrow:53,fnty:36,unsaf:[26,53,115,97,87,15,90,36],dw_tag_formal_paramet:[],movsd:7,argv0:90,culaunchkernel:11,ppcf128:36,emutl:[],simul:[94,36,88],dissassembl:42,movsx:94,commit:[],marshal:97,movsq:94,mrm7m:66,contriv:[108,128],f128:[36,66],down:[48,94,102,50,26,59,8,9,80,56,113,58,36,62,15,17,18,20,111,22,24,25,66,114,27,28,31,32,115,86,87,88,90,38,41,119,93,42,73,74,43,120],f3_12:66,indexreg:94,mrm7r:66,nomodref:58,insidebundl:94,subl:[94,7],parsesubtargetfeatur:66,precomput:58,perldoc:38,frameinfo:66,changeasciiint:42,xpass:2,imit:[127,46],ssl_do_handshak:42,editor:[38,43,101,127],fraction:[78,42,70,113],stage1:125,stage2:125,stage3:125,fork:4,numxform:20,creation:[],form:[],sub1:7,forc:[101,1,40,52,36,62,80,12,61,14,81,20,28,115,86,90,38,72,39,120,76,97],retarget:[56,94],llvm_:81,noun
 wind:[11,7,115,13,123,63,124,120,36],phid:101,emitbyt:66,shufflebyt:42,err2:20,autoinsert:20,addmoduleflag:25,bugfix:104,writeattribut:34,llvma:[],multisourc:[13,51,43,115,73],"__i386__":[26,15],unrel:[43,20,115,66,104],classid:46,classif:[4,36],featur:[],semicolon:[24,25,72,38,111,29,30,31,32,33,16,17,18,19,128,22,23],classic:[47,94,20],visitgcroot:82,diagnost:[],glanc:[101,26,15],dw_form_sec_offset:7,dwarfnumb:66,vista:[],shlib:38,excel:[38,81,20,66,58],image_scn_align_2048byt:121,a15:52,stackrestor:[],initid:124,subdivid:51,"0fc2d20000":11,iteri:[16,17,18,19,23],fell:5,libffi:[74,72],setinsertfencesforatom:53,furthermor:[48,114,36,47,40,7],pseudo:[],dcommit:[38,119],image_sym_type_int:121,n1720:101,skip:[101,1,40,36,80,115,81,16,17,18,19,21,22,23,24,25,66,82,27,111,29,30,31,32,33,88,94,122,124],"0x00000150":115,inlineasm:50,skim:101,createvirtualregist:94,mill:28,primer:72,pldi:82,hierarch:[48,124],misread:101,libit:28,fancier:[86,127],intermedi:[56,10,84,72,92,66,49,36,111,83,61
 ,82,14,120,124,68,40,20,108,22],targetinstrformat:66,hasinternallinkag:20,image_scn_align_2byt:121,letitem:46,memorymanag:9,mandlebrot:[],llvmbuilder:16,aspx:101,fnir:[24,25,29,30,31,32,33],string:[],bpf_add:94,create_argument_alloca:19,kernel_param_2:11,kernel_param_0:11,kernel_param_1:11,print_endlin:[16,17,18,19,22,23],initializealiasanalysi:58,did:[],dif:48,dig:[27,21,128],iter:[],item:[],s_load_dword:39,div:[94,20],round:[],dir:[38,72,49,42,2,12,115,105,125,36,51,64],initializealltarget:24,add_:81,sparclit:66,max_len:42,run:[],nozero:90,test_exec_root:2,sideeffect:36,addr:[89,5,36,66],addq:97,filler:47,insertbranch:66,favour:[8,110],addx:128,wors:[94,101,36,88],rephras:114,addi:[36,128],xml:124,deriv:[],livein:83,oversimplifi:20,elsev:[24,25,31,32,33],xmo:117,imul16rmi:94,wait:[101,39,49,111,30,126,4,62,22],box:[94,115,119],insan:101,canadian:38,shift:[48,57,50,28,94,70,63,124,36,8],max_total_tim:42,bot:[56,43,101,125],storeregtoaddr:66,extrem:[100,38,94,124,66,48,46,42,58,53,9
 3,86,43,36,78,128,20,59,115],bob:76,else_:[17,18,19],opcstr:66,stb_local:36,elect:43,bzero:5,modul:[],"__jit_debug_register_cod":109,patchabl:[40,36,97],"0baz":20,"0x60":107,perf:125,sake:[86,20],ruv:42,allocinst:19,use_llvm:[16,17,18,19,23],visit:[82,93,57,20,62],tokidentifi:46,deplib:124,perl:82,everybodi:[50,43],numfaultingpc:100,zeroargfp:128,"_ztid":36,checkout:[],rpath:38,fcomi:94,com_fir:94,"__atomic_fetch_and_n":53,appel:82,oop:40,examin:[85,66,36,28,94,93,13,105,40,104,20,62,9],effort:[85,48,57,101,29,115,43,97,63,4,108,23],fly:[111,94,30,9,16,22],reviewe:43,ulp:36,uniqu:[],imper:[101,82,31,33,17,19],sparcisellow:66,imped:36,nextvar:[24,25,31,32,33,17,18,19],nearest:[80,36],makefileconfigin:[],predict:[56,101,86,14,3,63],crazi:[27,28,26,15,21],subregion:36,agenc:0,exctype1:120,strikingli:[18,32],delete_funct:[16,17,18,19,23],subnorm:[36,11],binarypreced:[24,25,32,33],registerasmprint:66,ping:[50,43],f32:[14,94,36,66,11],idiv:94,image_scn_mem_read:121,till:[126,20,109],purg:
 101,foreach:[],pure:[48,71,66,40,29,53,43,44,94,46,23],ptr_is_nul:100,doclist:76,testingconfig:2,map:[],"__atomic_fetch_sub_n":53,max:[80,28,2,36],tmp9:[7,114],usabl:[66,28,94,115,87,20],intrus:[36,20],membership:[120,20],mag:36,mai:[],underscor:[83,101,115],maj:49,grow:[102,36,28,94,31,61,17,45,20,9],man:[13,38,28,72,56],noun:101,openssl_add_all_algorithm:42,"0x00001023":115,myglob:115,targetframeinfo:66,purifi:73,containingtyp:36,talk:[57,29,0,27,111,26,30,31,33,86,14,101,15,22,16,17,19,20,21,9,23],image_sym_class_automat:121,abbrevop0:124,abbrevop1:124,lsb:94,shield:[4,54,94],iptr:36,comdat:[],cppbackend:[],recoup:124,nbsp:94,gcmetadata:82,entiti:[],group:[],thank:[54,73],polici:[],build_shared_lib:72,mail:[],inlinehint:[36,124],image_file_machine_arm64:121,irbuild:[24,25,29,30,31,32,33,16,17,20,23],recoveri:[24,25,111,29,30,31,32,33,16,17,18,19,20,22,23],parseunari:[24,25,18,32,33],amdkernelcodet:39,remateri:53,sooner:126,initv:[24,25,33],lower16:35,possess:[80,20],lo16:94,ances
 tor:[36,113],getiter:[],xlc:38,crypto:42,careless:101,x11:20,myflag:76,misbehav:49,loopunswitch:48,compilecallbackmgr:[5,6],setdatalayout:[24,25,30,31,32,33],llvm_dylib_compon:[38,72],continu:[],redistribut:[],libgcc:95,tmp8:114,bpf_or:94,arcp:36,tmp7:[7,114],tmp6:114,tmp1:[101,7],tmp3:7,baselin:[94,104],simplecompil:[5,6,59,62,9],getbinarypreced:[24,25,32,33],catchret:[],"3rd":[42,36,9],createfil:25,bespok:82,numval:[24,25,27,111,29,30,31,32,33,124],dw_tag_unspecified_typ:[36,115],arminstrinfo:66,correct:[48,101,1,49,40,51,104,4,36,57,58,12,13,63,16,94,20,28,30,115,86,88,38,71,72,47,73,95,53,75,43,126],earlier:[80,66,47,29,30,53,63,44,36,62,9],"goto":[24,25,101,1,50,31,32,33,19],orr:36,tmpb:[24,25,33],ori:94,org:[38,101,0,102,119,56,49,83,42,29,12,96,76,13,75,14,43,126,72,104,51],ord:36,orc:9,may_throw:120,v8deprecatedinst:66,"_flags_":81,sn_mapr:50,createasmstream:94,thing:[],sn_mapl:50,principl:[101,117,50,27,4,21],think:[101,26,78,4,36,9,80,57,11,15,17,94,20,21,24,113,114,82,27,
 31,71,72,119,58,43],first:[],carri:[107,114,20,45,36,62],"long":[101,0,120,76,49,40,26,105,3,55,4,5,36,62,117,107,58,113,41,108,13,15,63,81,20,23,2,66,114,82,29,30,115,86,35,38,119,93,47,94,53,43,125],oppos:[38,71,36,28,37,17,46,64],getfoo:36,handleknownfunct:5,workaround:81,numop:[124,66],attrspellinglistindex:34,indiviu:94,indivis:61,numindic:80,averag:[24,17,42,31,55],daunt:72,"0f42d20000":11,broadcast:36,my_str:81,attrkind:[34,68],unpoison:36,getpredopcod:78,vbr6:124,vbr4:124,vbr5:124,vbr8:124,redefinit:[29,33,16,17,18,19,9,23],valuedisallow:28,exclusionari:102,were:[48,101,0,1,50,26,105,96,7,62,9,80,36,61,8,15,63,40,94,20,2,67,28,84,115,88,38,120,42,73,53,43,98,47],createlocalcompilecallbackmanag:[6,59],lcpi0_0:13,mcexpr:94,mrm5m:66,dw_tag_set_typ:115,llvmlibsopt:[],dash:[28,76,42],mageia:38,greet:128,gettargetlow:66,remotejit:5,r_arm_thm_movw_abs_nc:12,mrm5r:66,of_channel:[16,17,18,19,22,23],unadorn:36,weak_odr:[36,124],squar:[44,43,36,113,76],cumoduleloaddataex:11,llvm_target
 :[16,17,18,19],"_crit_edg":36,advis:[107,68,31,104,81,17],interior:[82,40,71,113],"0b1001011":128,channel:[56,5,102],sparciseldagtodag:66,llvm_analysi:[16,17,18,19,23],ptrloc:[82,36],pain:[28,20,119,109],ldststoreupd:94,trace:[71,40,28,115,86,42],normal:[],track:[48,101,50,2,36,8,94,58,41,108,63,40,18,19,20,23,25,82,29,115,32,33,86,38,93,42,73,43,97],allroot:51,cucontext:11,pair:[48,101,76,40,36,58,7,50,17,20,22,24,25,66,111,31,33,88,68,39,120,42,94,53,47],r31:[94,36],isphysreg:20,isglobaladdress:66,synonym:107,rtdyldmemoyrmanag:9,cumodulegetfunct:11,dw_form_:115,rev128:88,llvmgxx:[],isphysicalregist:94,defaultconfig:20,gracefulli:20,show:[],occumul:[],shoe:76,threshold:[48,14,36,105],corner:[47,97],getadjustedanalysispoint:58,emitexternalsymboladdress:66,dice:20,fenc:[],enough:[],argidx:25,frexp:36,adc64mi32:8,parametr:46,ftest:105,dict:42,hello_world:39,memmgr:[5,62],sourcewar:[75,42],intptr_t:[25,1,30,31,32,33],gep:[],html_cov_report:42,variou:[],get:[],mung:[48,114],secondari:[1
 20,43,97],repo:38,emitlabel:94,repl:[5,30,62,9],wheezi:[],fde:[94,71],gen:[],r10b:8,busiest:119,nullptr:[24,25,101,36,111,29,30,31,32,33,5,6,59,62,9],yield:[48,114,36,28,62,124,40,20,51],r10d:8,stupid:93,mediat:[0,58],r10w:8,wiki:[38,42,12,72],kernel:[],setpreservesal:86,"__builtin_setjmp":120,intrinsicsnvvm:11,assumpt:[25,101,120,36,26,115,87,15,40,94,7,9],lfunc_end0:39,sean:20,testcas:[20,29,43,41,36,23],immsext16:94,infinit:[48,42,94,36,58],parsedefinit:[24,25,111,29,30,31,32,33],nestabl:[46,128],innov:47,maskedbitset:76,datalayoutpass:25,enumer:[],label:[],behind:[],enumem:66,volatil:[],across:[48,1,40,26,55,36,8,11,14,15,63,81,16,20,28,30,115,86,88,38,71,120,42,94,53,97,44],arm64:38,august:85,parent:[],fpregsregisterclass:66,getdagschedul:[],rfunc:10,parseprototyp:[24,25,111,29,30,31,32,33],copyabl:20,false_branch_weight:3,llvm_enable_sphinx:[38,72],blocklen:124,audienc:[],library_nam:44,litloc:25,p0i64:7,improv:[48,50,26,104,36,9,58,59,14,15,63,40,16,2,66,82,30,115,86,38,119,1
 20,42,47],octeon:47,peephol:[57,94,30,31,32,33,86,16,17,18,19,20],among:[48,99,101,38,50,11,58,34,35,63,94,20],acceler:[],undocu:101,qeaa:120,unittest:72,tsflag:66,getnumsuccessor:101,cancel:120,iscal:[8,128],inadvert:[4,7],mctargetdesc:34,xadd:53,ultim:[101,49,2,30,16,36,8],createdatalayout:[24,25,30,31,32,33,5,6,59,62,9],p0i8:[36,11],mark:[],certifi:108,"0x4004f4":89,calledcount:93,llvmbitread:64,squash:[38,88],f92:11,runfunctionasmain:109,f90:11,f91:11,f96:11,f97:11,f94:11,f95:11,univers:[],f98:11,f99:11,those:[48,101,0,102,76,50,2,52,105,55,4,7,8,80,56,107,58,36,60,12,62,13,123,81,19,20,24,25,66,114,82,28,115,33,86,38,40,93,42,94,53,43,97,120,44,47],llvm_executionengine_orc_kaleidoscopejit_h:[5,6,59,62,9],sound:[42,9,58],isvararg:20,interoper:[82,36,26,53,15,120,20],desttool:[],"0x3feb":115,invol:120,"0x3fea":115,invoc:[38,41,72,36,42,94,93,86,125,122,7],isdoubl:128,gvneedslazyptr:66,advantag:[99,101,94,114,82,36,28,26,53,32,33,43,15,88,68,18,19,20,42],parse_expr:[16,17,18,19,22
 ,23],bytecode_libdir:[],destin:[24,25,107,66,120,94,33,13,3,63,19,36],llvm_gcc_dir:51,variable_op:128,add32mr:8,cudeviceget:11,liveoffset:82,same:[],ssl_library_init:42,image_file_machine_unknown:121,pad:[80,107,83,61,97,124,120,36],testrunn:2,pai:[13,43,101,66],oneargfp:128,add32mi:8,exhaust:[],assist:[101,73,32,63,18,118],executionengin:[38,19,109,59,47,94,62,16,17,5,6,20,18,9],capabl:[26,36,57,117,11,14,15,16,18,19,20,23,66,28,29,30,32,33,86,38,94,58,99],selecttarget:[5,6,59,62,9],kernel_code_entry_byte_offset:39,executeprogramandwait:4,runonmachinefunct:[],appropri:[48,101,0,76,49,40,2,104,78,4,59,8,9,57,94,11,113,36,12,63,18,19,20,111,22,66,82,28,115,32,33,86,88,68,38,119,120,58,53,43,126,99],macro:[],markup:[],v4p0f64:36,spadini:48,getobjfilelow:82,asmnam:66,dllvm_include_test:38,roughli:[71,113,120,94,53,104],emitleadingf:53,release_22:38,execut:[],speccpu2000:51,mo1:66,mul_ri:128,mygcprint:82,subblock:124,aspect:[25,29,72,82,46,47,26,31,115,54,43,15,36,17,94,20,111,22,23],mu
 l_rr:128,flavor:[36,20,115,128],runtim:[],"125000e":36,xxxtargetmachin:66,critial:104,param:[101,11,82,2,126,96,16,17,18,19,20,23],cumoduleunload:11,sparcregisterinfo:66,"__cxa_throw":120,rcindirectstubsmanag:5,dclang_tablegen:12,setrequiresstructuredcfg:66,mcregaliasiter:94,mov:[11,36,47,94,53,35,7],coverage_pc:[],mod:[],cast_or_nul:20,is_ptr64:39,ifstream:11,qnan:36,server:[47,5,20,42],bb0_4:11,bb0_5:11,prologuedata:124,halid:47,bb0_2:11,physreg:94,maybeoverridden:50,mappingnormalizationheap:76,fulfil:[4,113],exitcod:2,createremotememorymanag:5,fastcal:[94,36],ascend:[80,36],substitu:13,llvm_enable_doxygen_qt_help:72,adequ:[82,96,72,66],confirm:[42,101],llvmscalaropt:64,recomput:[86,20,58],ffi_library_dir:72,"__llvm_stackmap":97,inject:101,dw_op_plu:36,ret_val:[16,17,18,19,23],overli:43,broken:[86,56,108,66,40,47,2,13,43,88,20,128],cuinit:11,selectaddrrr:66,cornerston:114,x32:7,x30:36,dw_ate_address:36,island:[117,39],loadinst:101,pluginfilenam:90,deopt:[40,36],llvm_targets_to_bui
 ld:[38,96,72],road:[],livecount:82,noth:[86,48,0,114,82,27,94,33,13,36,4,19,20,21],hashtbl:[16,17,18,19,22,23],strip:[],"0x3fe9":115,ymax:[18,32],mingw32:[13,126,94],"__cudacc__":14,overwrit:[28,97,64],compliant:14,int_stacksav:36,legalact:66,savethi:7,x86inst:8,llvmattributeref:47,source_x86_64:89,uintptr_t:5,dw_ate_boolean:36,jite:[56,6,59,9,109],gori:43,buggi:73,stringmapentri:20,runtest:[49,12],reappli:43,possibl:[],optnum:28,poolalloc:58,unusu:[94,82,26,95,15,20],sanitize_address:36,embed:[],i32mem:128,emitpseudoexpansionlow:34,filt:105,machinefunctioninfo:[83,94],emitloc:25,threadloc:[36,124],subprogram:[25,36,115],deep:[],simpletyp:121,"__sync_fetch_and_add_n":53,deem:[57,73,36,104],emitvalu:94,proport:[28,122],fill:[24,25,73,58,27,28,29,30,31,32,33,86,101,111,36,126,76,20,47,115],again:[50,51,26,104,36,9,7,15,63,81,16,17,19,20,28,29,30,31,33,86,88,120,42,73,95,125,127],mangler:[66,5,6,59,62,9],know:[],field:[],"_cxxthrowexcept":120,xxxgeninstrinfo:66,"0xc0de":124,riinst:128,
 architectur:[],reextern:[16,17,18,19,23],"0th":114,sequenc:[],arrayidx:36,f93:11,descript:[],v2f64:36,version_less:72,winzip:96,getreturntyp:20,unset:[25,46,72,81],insertbefor:20,forget:[25,101,102,113,82,119],mrm3m:66,dollar:52,dw_form_ref2:115,sunk:58,llvmdummyasmprint:66,dw_form_ref1:115,regno:94,mrm3r:66,dw_form_ref8:115,children:113,tag_structure_typ:115,image_sym_class_clr_token:121,at_byte_s:115,cmake_c_compil:38,daniel:115,brtarget8:66,immt:8,image_scn_lnk_comdat:121,r14:[94,8],r15:[83,94,36,8],r12:[36,94,35,8],r13:[94,8],r10:[94,95,8,11],r11:[95,36,8,97],fals:[48,101,50,2,54,3,78,5,6,59,62,9,113,58,36,115,108,12,17,20,24,25,66,28,29,30,31,32,33,86,34,89,90,38,93,122,41,99],offlin:[94,11],util:[],seprat:42,fall:[24,25,101,66,48,82,20,28,30,31,32,33,36,40,16,17,18,19,7,70,9],"0x629000004748":42,"__clear_cach":36,basereg:94,sin_port:5,run_funct:[16,17,18,19],dispel:114,egg_info:51,dereferenceable_or_nul:36,gcno:105,use_end:20,stderr:[],fuzzerinterfac:42,quiet2:28,webkit_jscc:[
 36,124],rawfrm:[66,128],globalalia:86,lawyer:43,val3:36,val2:[42,36],val1:[42,36],val0:36,val7:36,excit:[47,26,15,104],abc:36,parsedattrinfo:34,close_fd_mask:42,abi:[],debug_pubnam:115,abl:[],invok:[],cont6:120,abu:107,g0l6pw:38,hurdl:108,exit5:11,cumemcpydtoh:11,logerrorv:[24,25,29,30,31,32,33],valc:11,variat:[94,66,58,120,42,1,4,127,9],vala:11,sophist:[82,51,94,86,127,36],analysisusag:[],memory_order_acquir:[36,53],writetypet:57,variad:101,lltok:57,valu:[],quieta:28,search:[],unabbrevi:124,image_rel_amd64_sect:35,createfcmpon:[24,25,31,32,33],r12w:8,p0v8p0f_i32f:36,r12b:8,val_:19,r12d:8,codebas:[101,119],narrow:[38,57,101,114,58,93,73,53,41,20],iuml:94,quotient:36,primit:[],transit:[],inappropri:0,establish:[66,82,40,94,43,63,120,16,36],memor:101,initializenativetargetasmprint:[25,30,31,32,33,5],mylib:[],zeroiniti:36,mfloat:12,tackl:[16,19,30,108,33],two:[],x86targetasminfo:66,getbit:28,saptr:36,desir:[48,101,0,40,26,78,36,8,85,7,13,15,63,20,2,66,82,28,115,86,35,72,93,53,97],upper
 16:35,penultim:66,reconfigur:[],particular:[48,73,0,50,51,2,105,101,36,8,80,94,11,113,61,13,63,40,16,19,20,111,22,85,66,114,82,28,30,115,33,86,34,38,72,93,42,58,53,123,97,124,120,44,46,47],ultrasparc:[38,66],dictat:[95,101,20],none:[94,40,2,104,78,4,36,107,14,16,17,18,19,20,22,23,114,82,28,86,89,90,38,120,73,128],hour:[0,125],dep:[16,17,18,19],elsebb:[24,25,31,32,33],dev:[101,40,26,56,57,12,13,15,63,20,24,82,83,115,86,87,90,119,53,43,46,128],remain:[48,101,0,40,104,36,9,80,107,7,13,18,19,20,82,83,115,32,33,72,120,53,43,97,124,128],paragraph:[50,101,127],deb:12,binfmt_misc:38,def:[],share:[],sln:96,loopend:[24,25,31,32,33,19],mcobjectstream:94,minimum:[38,57,101,72,66,36,47,73,96,41,115,54,43,97,81,59,111,22],explor:[40,20,119],dw_ate_unsign:36,strlen:20,retcc_x86_32_ss:66,calltmp1:[17,29,31,23],calltmp2:[16,30],kcc:[],awkward:[28,101,114],secur:[48,28,30,56],programmat:[82,122,11],comfort:[50,0],csx:42,cst:36,csv:51,bar_map:101,regener:[73,104],runtimedyldimpl:85,number2:50,number1:
 50,my_function_precis:11,memory_order_seq_cst:[36,53],bloom:94,ccpassbyv:66,sse4:1,binloc:25,sse2:[13,36],mislead:101,hfc:100,cs1:[36,58],roots_siz:82,takeerror:[5,20],rotat:[],intermediari:20,isconstantpoolindex:66,mydoctyp:76,through:[],suffer:82,llvm_src_root:[51,64],patfrag:66,pch:115,ssl_free:42,realpr:36,good:[],pollut:101,compound:80,nor:[48,101,114,82,50,42,94,96,97,124,120,4,36,47,108],adventur:20,complain:[],cmpflag:50,mysteri:114,micro:101,token:[],findsymbol:[30,31,32,33,5,6,59,62,9],looputil:86,distdir:[],subsystem:[],harm:94,mental:102,mm5:[8,128],unequ:36,mm7:[8,128],hard:[],mm1:[8,128],idea:[],functor:[101,62],mm2:[8,128],image_file_machine_thumb:121,connect:[48,71,119,126,5,20,9],orient:[101,102,113,26,115,15,20],sparcgenregisterinfo:66,usedlib:64,handleerror:20,dw_tag_xxx:115,isref:128,variable_nam:72,dagcombin:57,isinlin:115,cconv:36,mmx:[94,36,66],intregssubregclass:66,suspici:4,b32:11,cuctxdestroi:11,mmi:83,dw_tag_union_typ:[36,115],omit:[48,10,94,106,103,42,84,
 31,122,86,87,97,55,89,17,69,37,36,111,22],intermingl:36,buildmast:126,testfnptr:36,llvmgccdir:51,vmov:7,perman:0,"__c_specific_handl":120,callon:20,registerasmstream:94,printsth:48,exchang:[38,20],harfbuzz:42,argstart:28,done:[48,101,76,49,50,51,52,104,78,4,5,6,59,62,85,57,107,36,115,109,13,123,40,16,17,18,19,20,111,22,23,24,25,84,113,82,99,28,29,30,31,32,33,86,72,119,93,42,94,95,53,43,120,46,128],dylib:[74,13,5,6,59,62,9],stabl:[66,20,60,104,43,99],rootnum:82,your_lib:42,image_sym_type_uint:121,somewhatspecialsquar:113,expansionregiontag:80,least:[48,101,49,40,2,52,104,36,107,58,12,13,16,17,18,19,20,111,22,23,24,25,66,28,29,30,31,32,33,34,88,38,120,42,94,53,43,97,124,128],createpromotememorytoregisterpass:[25,33],is_arrai:111,unalign:[63,53],memset:[],binop:[24,25,111,29,30,31,32,33,16,17,18,19,22,23],selector:[],part:[48,101,0,76,50,26,96,111,5,6,59,8,9,113,58,36,115,62,13,14,15,63,81,16,17,18,19,20,21,22,23,25,2,66,114,82,27,28,29,30,31,32,33,86,34,88,38,41,72,40,93,42,94,53,43,1
 24,120,44,99],pars:[],toc:94,contrari:94,cyclic:38,i32:[],"_tag":[16,17,18,19,22,23],horizont:7,i8mem:94,"_runtim":97,fpinst:8,constval:20,timeout_exitcod:42,xxxtargetlow:66,uncontroversi:82,compileutil:[5,6,59,62,9],char6:124,debug_loc:98,createalloca:[24,25,33],writeonli:36,built:[],zero:[],push_back:[24,25,101,66,76,59,111,29,30,31,32,33,5,6,20,62,9],build:[],extractel:[],cleanuppad:[],gettransform:62,distribut:[],significand:36,previou:[],chart:1,took:[47,16,17,18,19,23],most:[],cygwin:[38,96,94],image_file_machine_i386:121,charg:94,dimension:[18,114,32,11],addsdrr:128,emitandfin:62,"234000e":[29,23],resolvereloc:85,t2item:50,sector:4,visitbasicblock:20,carefulli:[82,115,33,43,63,19,36],llvmaddattribut:47,"__sync_val_compare_and_swap_n":53,"__try":120,particularli:[101,66,7,53,86,63,36,20],fine:[],find:[],realmag:[18,32],merger:50,filesizepars:28,printmemoperand:66,hasctrldep:[8,128],unus:[],express:[],cheaper:[100,20],"__cuda_arch__":14,wrinkl:[61,62],restart:[86,126,42,20,53],
 misnam:94,uncomfort:102,detect_leak:42,catcherror:20,mycustomtyp:76,image_file_machine_arm:121,diloc:[],common:[],expr:[24,25,10,118,111,31,32,33,16,17,18,19,22,23],functionindex:68,intptrsiz:82,"__nv_isnanf":11,printout:[84,20],decompos:[57,43],reserv:[100,66,40,42,94,104,97,124,36],mrm1m:66,ccdelegateto:66,dispatch2:[120,36],dispatch1:36,someti:36,initializemodul:25,debat:101,smallest:[73,36],"0b1234567":[],subscript:[48,36,58],experi:[72,102,50,30,52,115,40,16,127,62,9],altern:[],dw_at_apple_property_gett:115,bourn:[38,28,108],appreci:43,complement:[36,20,114],kryo:47,unrol:[],popul:[38,57,2,11,120,42,29,34],findsymbolinlogicaldylib:9,uniprocessor:53,alon:[28,94,13,43,111,22],foreign:[108,72,9],densemapinfo:20,cpufreq:52,allocs:36,libcrypto:42,simpli:[48,101,40,51,4,36,62,107,58,7,108,12,13,16,20,111,64,23,84,66,114,28,29,30,115,86,38,119,93,94,43,97,22,120,45],fldcww:94,point:[],instanti:[85,76,113,66,28,2,86,105,34,20,8,128],linkagenam:36,alloca:[],shutdown:42,suppli:[],setinte
 rnallinkag:20,throughout:[80,85,124,38,88,81,4,36],backend:[],global_begin:[101,20],dovetail:[19,33],aarch64:[],linkonce_odr:[36,63,124,11],retq:[40,83],val1l:36,globalvarnam:36,reformat:45,multiclassobject:46,debug_nam:115,image_sym_class_extern:121,lto_codegen_add_must_preserve_symbol:99,unnecessarili:[86,58],gap:[101,36],understand:[],repetit:94,isstoretostackslot:66,dw_tag_string_typ:115,noexcept:120,autoregen:[],unifi:[],fun:[27,26,35,15,16,17,18,19,21,23],everyon:[15,43,26,0,101],subsect:[],propag:[],lto_codegen_add_modul:99,mystic:[26,15],semispac:82,itself:[101,0,120,76,49,50,2,105,54,5,6,59,62,9,57,94,58,36,115,108,12,61,13,15,63,40,16,17,18,19,20,111,22,23,24,25,26,113,67,82,28,29,30,31,32,33,86,88,114,38,41,72,99,42,73,96,43,97,124,125,44,46,47,128],codegen_func:[16,17,18,19,23],swiftcc:[36,124],"0x00007ffff7ed40a9":109,case_branch_weight:3,myseqel:76,incarn:57,benign:51,getlin:[25,115],flag2:[50,42],flag1:[50,42],nameflag:115,multicor:53,keyr:38,"0x3fed":115,sym:[49,37,3
 5,5,6,59,62,9],keyt:20,moment:[82,40,83,36,59,23],travers:[],task:[],n_bucket:115,entri:[],"16mib":35,globalisel:47,uint32_t:[5,76,115],spend:2,instr_begin:19,explan:[0,113,39,50,108,72,36],llvm_target_definit:66,obscur:[36,20],ldl:14,shape:[115,20,8,113,104],at_decl_lin:115,depriv:20,stwu:94,cut:[28,66,9,70],shiftinst:101,snan:36,singlesourc:[13,51],"0b000000":66,restructuredtext:127,objectbodi:46,largeconst:97,dllvm_experimental_targets_to_build:66,realloc:[54,58],rgm:86,postcal:82,bin:[38,105,49,41,28,12,52,13,75,96,42,125,8,64],bio:42,xcodebuild:72,llvmsetinstrparamalign:47,llvm_tarball_nam:[],judgement:43,transmit:36,fucomip:94,irgen:[5,6,63],phinod:[24,25,101,31,32,33],ccassigntoregwithshadow:66,knock:101,writealia:50,semi:[44,82,26,15,81],sema:34,wit:0,adc32mr:8,aliasset:[66,58],often:[],steensgaard:58,weakodrlinkag:20,dllimport:[36,124],bach:4,dw_apple_property_null_resett:115,"0x00002000":115,mirror:[],sizeof:[],sparcreg:66,compilecallbackmanag:[6,59],per:[76,40,51,54,55,36
 ,62,80,107,11,13,20,113,82,28,115,86,34,70,72,99,42,94,53,37,97,124,120,44,46],pem:42,substitut:[],mathemat:[11,50,111,108,36,22],larg:[],chandlerc:119,cmake_instal:72,reproduc:[42,73,33,13,43,19,93],createentryblockalloca:[24,25,33],either:[48,73,0,120,50,51,26,104,101,111,84,36,8,9,85,57,107,11,62,13,123,15,63,40,16,17,94,20,21,22,25,112,2,66,114,82,27,28,29,31,87,88,89,38,93,42,58,53,75,43,97,124,83,47,128],intial:20,browsabl:72,patient:[86,102],dw_tag_template_value_paramet:36,initialse:79,oeq:36,adc64rr:8,s15:36,fnstart:94,adc64rm:8,addpdrm:128,float_of_str:[16,17,18,19,21,22,23],selp:11,impos:[0,36,94,43,97,83,20],constraint:[],preclud:[40,88],createfadd:[24,25,29,30,31,32,33],litconfig:2,"0x00001c00":94,disclosur:[43,0],timberwolfmc:51,fmin:36,add32mi8:8,ostream:[101,20],nsz:36,frames:82,n2242:101,"0x1c2":35,inclus:[],hydra:125,errno:[36,58],megabyt:41,x86_fastcallcc:124,subst:[46,8,128],includ:[],cptmp0:66,cptmp1:66,forward:[48,101,40,4,36,57,58,20,21,22,23,82,27,111,31,115,
 68,120,94,124,46,128],image_scn_align_1byt:121,micromips32r6:47,myservert:5,reorgan:76,"0x00000003":115,dwarfdump:[],int8_t:76,translat:[48,101,26,36,80,106,58,108,15,63,94,20,25,66,114,28,115,34,38,76,53,118],llvmfoldingbuild:16,codeblock:82,concaten:[38,88,46,13,36,20,128],internaltarget:[],tvo:47,exported_symbol_fil:[],regconstraint:94,movnt:36,v8i16:66,"0x00000009":115,glibcxx_3:38,curs:[41,2],attrinfomap:34,metal:36,somemap:101,image_file_machine_amd64:121,functioninfo:100,codgen:23,isdigit:[24,25,27,111,29,30,31,32,33],prevail:107,singli:82,cmake:[],crypt:43,sequenti:[],abbrev:[98,124],llvm_target_arch:72,bpf_rsh:94,vg_leak:2,asymmetr:114,deseri:34,image_scn_lnk_remov:121,functionnod:50,mismatch:[],globalvar:124,orcabisupport:5,formatt:36,tok_numb:[24,25,27,111,29,30,31,32,33],libtool:[],deserv:[36,63],image_sym_type_float:121,image_comdat_select_associ:36,machine_version_step:39,debugloc:[25,94],downcast:113,i16:[94,36,66,11],tradeoff:[16,82,30,53],required_librari:44,dwarfre
 gnum:66,"0fb5bfbe8e":11,queri:[],strex:53,regallocregistri:86,demangl:[89,105,37,115],privat:[],antisymmetr:50,ulimit:42,elsewher:[40,66],createtargetasminfo:66,granular:4,saga:[17,31],istream:20,exit:[],priority_queu:20,loopinfowrapperpass:86,bpf_sub:94,immsubreg:66,disclos:0,named_valu:[16,17,18,19,23],"0xe413754a191db537":80,cudeviceptr:11,volum:[56,20],implicitli:[101,1,26,111,36,15,81,16,17,18,19,20,21,22,23,24,25,27,28,29,30,31,32,33,86,94,76,43,97,124,46,128],ilist_half_nod:[],flagscpu2:76,parenthandl:36,postord:71,stddef:42,knight:47,refer:[],pbqp:[94,87],"0x9":94,"0x8":94,fortun:[24,101,26,30,31,33,15,16,17,19,20],veli:94,"0x3":[97,94,20],segmentreg:94,"0x1":[97,94,20,115],"0x0":[94,20,124,39],toplevelexpr:[24,25,111,29,30,31,32,33,16,17,18,19,22,23],"0x6":94,"0x5":[94,97],"0x4":[94,97],arcpatch:119,append:[72,107,36,106,13,105,124,41,17,20,64,128],"0x1f84":89,resembl:114,unwound:36,access:[],agg1:36,agg3:36,agg2:36,deduc:[],camlp4:[21,22],sint:36,bodi:[],dw_macinfo_defin:3
 6,"0xh":36,sink:[],"0xm":36,jonathan2251:65,"0xc":[94,124],"0xb":94,getsourc:38,sine:[36,66],"0xf":128,llvm_abi_breaking_check:72,"0xd":[94,124],remark:[93,1],libc:[38,101,36,42,26,43,15,20,47],fpregsregclass:66,cerr:11,irreduc:[48,66],foundat:[86,43,0,102,9],mov64ri:66,tool_nam:38,quickstart:[],toshio:94,seamless:75,advoc:[101,102],projlibspath:[],select_isd_stor:66,"_regoffset":8,at_encod:115,elfv1:47,elfv2:47,bpf_jne:94,trait:[101,20,76],attrspel:34,image_scn_align_512byt:121,undefinedbehaviorsanit:42,trail:[80,101,114,76,7,28,2,36,81,20],train:[122,125],account:[38,0,102,119,82,50,126,43,113,36],dcmake_c_compil:42,komatsu:94,rdynam:[18,19,30,32],obvious:[48,57,101,114,58,49,27,28,94,86,43,111,36,50,20,21,22,128],ch8:[],ch9:25,unread:[101,53],fetch:[38,54,3,36,94],aliv:[86,48,94,20,50],n2657:101,abcd:124,sqlite:42,tarbal:[56,12,104],virtualindex:36,msvc:[101,120,111,94,115,35,81,20],formmask:66,predicate_stor:66,everywher:[13,16,76,30,50],add32ri:8,rootcount:82,dw_at_apple_proper
 ty_attribut:115,add32rm:8,inteldialect:36,gcn:[94,39],ssl_ctx_use_privatekey_fil:42,list_nam:81,smovq:94,add64mr:8,tag_memb:115,act:[48,101,0,50,42,94,115,70,36,20,62],getehframesect:85,inst:[48,42,20,66,128],getsigjmp_buftyp:101,llvm_include_dir:72,redund:[],bind:[],correspond:[48,101,76,50,96,111,78,7,8,80,57,113,11,36,60,123,40,17,94,20,108,22,23,25,112,66,114,82,83,28,29,31,115,86,87,35,88,89,38,71,72,119,93,73,53,43,124,120,46],afterloop:[24,25,31,32,33,17,18,19],region1:80,region0:80,noitin:90,fallback:[54,124],loopendbb:[24,25,31,32,33],writethunkoralia:50,declet:36,machineconstantpool:94,deallocationtypemismatch:54,mybuilddir:72,cpu_x86_64:76,bunch:[27,51,108,30,125,32,81,16,18,20,21],acycl:[94,71,115,66,118],fpcmp:51,outputdebuginfo:28,ilp32:[26,15],labor:28,i1942652:36,list_of_list:81,typemap:57,objmakefil:[],clientaddr:5,basic_ss:128,greater:[48,114,101,124,66,11,82,50,47,94,105,3,88,55,5,36],passnam:84,grpc:42,dbgopt:115,spell:[43,34,101],dai:[56,72,38,26,104,43,15,20],m
 ention:[124,56,101,0,88,39,113,50,28,94,95,115,36,40,44,72,20,128],symbol1:35,nval:36,mylist:76,isimplicitdef:8,strive:[13,101,102],createfcmpult:[24,25,29,30,31,32,33],parseexpress:[24,25,111,29,30,31,32,33],mem2reg:[],destarchivelib:[],dwo:98,dllvm_libdir_suffix:72,add16ri8:8,lie:[40,28],getloopinfo:86,ssl_filetype_pem:42,ddi0419c:117,cmake_module_path:72,addtypenam:20,llvmsupport:[38,64],usernam:[38,43],fluctuat:58,sexual:102,rex:36,paramattr:124,start_val:[17,18,19],createmyregisteralloc:86,dllvm_enable_backtrac:38,rev:[104,88,16,17,18,19,22,23],ret:[],stub:[117,66,20,94,50,5,6,59],typenam:[5,20,62,111],stuf:7,rel:[38,101,72,122,82,28,2,104,35,63,124,55,94,7,70],rem:94,image_file_machine_powerpc:121,rec:[16,17,18,19,21,22,23],dw_apple_property_assign:115,ref:[],reg:[66,11,83,94,7,97,45,20,128],red:36,clarifi:[40,115],deregisterehframesinprocess:5,workflow:[119,125],qux:36,thejit:[25,30,31,32,33],standalon:[44,25,26,94,27],jacqu:14,cmake_install_prefix:[38,96,12,72],invas:[43,76]
 ,afterward:[48,63,40],setinsertpoint:[24,25,29,30,31,32,33],retain:[71,20,28,108,86,54,43,88,36],ud2:94,suffix:[86,57,29,72,66,39,36,28,2,87,107,13,105,101,103,106,5,6,20,23],createcompileunit:25,pgo:[],targetregsterinfo:94,pgr:56,ualpha:46,secondlastinst:66,facil:[101,58,82,28,2,115,96,4,108,64],misoptim:3,llvm_enable_eh:72,ancient:125,dllvm_use_sanitize_coverag:42,habit:[48,101],target_data:[16,17,18,19],messag:[],sadli:119,dw_apple_property_sett:115,adttest:72,llvmusedlib:[],lookuptarget:24,comparefp:128,gear:72,ogt:36,mytool:[],s31:36,s32:11,pg0:50,pg1:50,"__objc_imageinfo":36,nontempor:36,image_file_aggressive_ws_trim:121,source_i386:89,rpass:1,structur:[],ssl_ctx_use_certificate_fil:42,"123mb":28,then_val:[17,18,19],machinemoduleinfo:83,plaintext:[],thereaft:97,subclassoptionaldata:50,ehobj:120,createtargetmachin:24,immigr:102,have:[],tidi:86,llvm_build_dir:38,bpf_jsge:94,min:[49,42,36],mib:35,mid:[36,61,63],in64bitmod:94,sspreq:[36,124],mix:[],builtin:[],bpf_jsgt:94,mip:[],pa
 rsetypetyp:57,mit:43,isloc:[36,115],poison_yet_again:36,unless:[48,101,0,120,40,51,104,105,36,10,7,13,63,81,17,19,20,66,114,82,28,31,33,86,87,72,92,39,93,42,43,97,125,127],freebsd:[38,47,94,104],fcuda:14,nativeptrt:5,setpreservescfg:86,eight:[94,36,107],transcript:[16,30],v8i32:36,arm_aapcs_vfpcc:124,gather:[],thunderbird:43,image_file_machine_mipsfpu16:121,belevich:14,getdirectori:[25,115],institer:20,llvmcreatejitcompil:[],instantiatetemplateattribut:34,occasion:[82,124],removemodul:[30,31,32,33,5,6,59,62,9],addpassestoemitmc:85,manglednamestream:[5,6,59,62,9],dllexport:[36,124],retainedtyp:[36,115],ifconvers:66,text:[],ifconvert:66,empir:14,sanitize_thread:36,targetpars:47,llvm_map_components_to_libnam:72,staff:0,dw_tag_pointer_typ:[36,115],textual:[71,87,94,30,13,105,34,43,16,45,128,36,8,108],loweroper:66,src_root:38,"__morestack":95,cpunam:[90,87],inferior:109,data64bitsdirect:66,print_newlin:[16,17,18,19],lower_bound:20,litvalu:124,sysv:[37,117],disagre:[36,102],bear:7,is_base
 _of:113,image_sym_class_member_of_struct:121,increas:[48,73,1,29,101,54,43,63,110,90,99,8,23],organ:[],at_end:[16,17,18,19,23],callpcrel32:128,integr:[],cudamemcpydevicetohost:14,conform:[38,101,76,82,59,2,87,36,20,62,108],project_nam:64,emitfnstart:94,ssl_ctx:42,dw_tag_file_typ:115,femult:[],"0x00000233":7,athlon:24,dpython_execut:52,reform:101,pattern:[],boundari:[48,124,36,94,30,53,88,20],llvmcreateinterpret:[],progress:[71,72,82,27,2,104,43,36,83,117,94,20,21],"0b100":128,"0b101":128,switchtosect:94,nvptx64:11,phase3:49,plugin:[],joke:102,equal:[101,50,3,36,113,58,108,63,17,18,19,20,111,22,24,25,66,28,31,32,33,70,39,120,94,124,128],instanc:[],freeli:[43,53],venu:0,guidelin:[],vend:61,functionnam:[82,36],v2i32:36,much:[48,73,0,76,49,40,26,101,55,4,36,8,57,94,11,113,108,12,61,116,62,13,14,15,63,16,19,20,111,22,23,66,99,28,29,30,115,33,86,107,38,119,93,42,58,53,74,75,43,97,64,126,127,46,47],gc_transit:40,endforeach:81,json:51,defini:78,addresssanit:[42,36],type_info:120,autovector:
 1,component_1:44,component_0:44,createmul:20,bulk:[94,19,20,33],untyp:83,"__sync_fetch_and_umax_n":53,determinist:[58,20,42,94,34,125,93],multi:[],plain:[86,127,20,9],baselay:62,defin:[],image_sym_class_argu:121,operandtyp:66,ill:107,func_typ:40,helper:[101,50,2,111,36,9,85,58,115,13,18,19,20,21,22,23,24,25,66,28,29,30,31,32,33,34],almost:[57,71,82,40,94,101,53,43,63,88,4,20],virt:20,srand:42,maystor:8,isreturn:[8,128],multimap:20,substanti:[101,58,82,30,16,36],fiddl:[20,127,12],unneed:[19,33],llvm_enable_zlib:72,japanes:38,addmoduleset:[5,6,59,62,9],"__cxxframehandler3":120,promoteop:57,codepath:53,infer:[101,113,67,40,94,76,14,87,63,88,90],backtrac:[25,94],cmakecach:[72,81],valueopt:28,dealloc:[82,36,54,20],add_dep:81,sm_30:94,image_scn_align_32byt:121,sm_35:[14,94],center:25,neural:51,nevertheless:36,getopcod:[20,66],builder:[],col:25,thought:[],setp:11,choos:[94,0,102,78,36,9,41,12,20,111,66,82,27,28,30,31,115,86,88,90,72,119,47,73,43,126],error_cod:[24,20],latest:[38,119,49,47,
 96,7],test1:[13,40,127],tarjan:86,test5:7,listconcat:[46,128],numberexprast:[24,25,111,29,30,31,32,33],p18:11,settabl:[],f_none:24,tough:[111,22],kwd:[16,17,18,19,21,22,23],adt:[],lako:101,add_cfg_simplif:[16,17,18,19],memorymanagerptrt:62,onward:72,uwtabl:[36,115],add:[],cleanup:[],getsymboladdressinprocess:[5,6,59,62,9],voila:42,ada:120,dced:20,c11:[14,53],createbasictyp:25,smart:[101,36],apple_typ:115,hypersparc:66,fnscopemap:25,pcre2posix:42,image_file_net_run_from_swap:121,punctuat:[36,101,46],realiz:[16,18,57,32],positionaleatsarg:28,canlosslesslybitcastto:50,clang_bootstrap_cmake_arg:125,insert:[],checkerrorcondit:20,success:[101,76,5,6,36,41,16,17,18,19,20,22,23,24,25,66,67,111,29,30,31,32,33,86,38,120,73,43],sstream:101,registeranalysisgroup:[],inferenc:94,c1x:36,stlextra:[24,25,29,30,31,32,33,5,6,59,62,9],soft:[],crawler:82,unreach:[],vec01:36,convei:[82,120,43,36,63],registermcobjectstream:94,"_m4enum":36,proper:[80,101,113,66,20,2,53,36],getparamtyp:20,release_1:38,tmp:[
 72,114,82,20,94,30,33,13,89,36,16,19,7,64],incant:14,nvcc:94,llvmrock:101,esp:[47,94,7,8],nvcl:11,llvmaddfunctionattr:47,nonempti:36,"__internal_accurate_powf":11,dw_tag_structure_typ:[36,115],notail:[47,36],prose:101,image_scn_lnk_nreloc_ovfl:121,dce:[],word32:94,noisi:[48,43,20],host:[],"0xffff":[97,36],geometr:[26,15],simpler:[48,57,94,115,32,33,18,19,36,9],about:[],actual:[100,48,101,88,76,49,50,51,26,54,111,4,5,6,7,62,9,85,107,58,113,59,115,108,13,14,15,63,81,16,17,18,19,20,21,22,23,25,2,66,114,82,27,28,29,31,32,33,86,126,36,71,40,93,42,94,53,43,64,124,120,44,128],socket:5,discard:[38,36,28,94,35,20,47],addendum:56,orcx86_64_sysv:5,vocabulari:36,guard:[101,35,63],getglobalcontext:[],ifexpr:[24,25,31,32,33,17,18,19],leverag:[82,38,20],mm0:[94,8,128],rcx:[94,36,8],eh_fram:120,naveen:48,rcn:49,getelementptrinst:20,"__cxxthrowexcept":120,biggest:[94,61],calltwo:20,macinfo:36,mm3:[8,128],d18035:47,functionlisttyp:20,unexpect:[101,50,51,33,96,43,81,19],f4rc:94,bur:71,brand:86,machine
 functionpass:[],bui:52,bug:[],wise:36,mcpu:[39,66,11,12,52,13,87,90],wish:[38,57,73,0,119,66,114,50,28,2,14,63,36,40,72,20,128],unload:[86,36],srcarglist:36,flip:101,install_prefix:72,"__nvcc__":14,emitjumptableinfo:66,sockaddr:5,pin:[40,36],sin_famili:5,hashfunctiontyp:115,dure:[],pic:[94,66,47,73,12,115,90],encompass:[52,68],int64_t:[76,20],pf_inet:5,extra_sourc:81,llvm_append_vc_rev:72,guidanc:[101,63],detail:[],virtual:[],dw_apple_property_strong:115,argumentlisttyp:20,apple_objc:115,gcc:[],zeroormor:28,escap:[38,58,82,46,32,13,99,36,120,18,7,45],ksdbginfo:25,al_aliasset:66,testcaselength:20,afterbb:[24,25,31,32,33],kw2:42,predsens:78,"_zfoov":36,unshadow:[24,25,31,32,33,17,18,19],"_ztv3foo":7,eliminateframeindex:66,liveout:[40,97],n2756:101,poorli:[101,70],bpf_arsh:94,getreginfo:94,undef:[],patcher:97,isvi:66,spec:[76,20,51,73,115,104,13,36,83,46,128],bb0_1:11,add_incom:[17,18],concret:[],under:[101,40,26,5,6,59,62,9,80,11,36,108,61,8,13,123,15,63,111,22,65,2,66,28,86,126,38,41
 ,72,119,120,42,94,75,43,125,44],emitloadlink:53,testabl:119,playground:[27,21],everi:[],risk:[36,52,104],f934:66,rise:101,risc:[94,53,66],implicit:[],mo_registermask:94,printfunctionpass:48,llvm_yaml_strong_typedef:76,mygc:82,verif:[],llvmparsebitcodeincontext:47,isdefinit:[36,115],x86_64:[],properti:[],dw_form_ref4:115,xxxinstrinfo:[78,66],codeviewdebug:115,naiv:48,enjoi:126,xf8:42,xor32rr:[83,94],llvm_yaml_is_document_list_vector:76,xf7:42,hide:[],introspect:[40,45,99,36,68],foundfoo:101,hi16:94,conduct:[],asymmetri:[100,50],functiontyp:[24,25,29,30,31,32,33,20],studio:[],path:[100,48,101,40,51,2,52,105,96,36,9,107,11,41,12,13,14,116,63,81,19,20,64,112,67,82,33,86,87,89,90,38,72,120,42,58,53,122,75,125,118],dlopen:86,forum:[56,36,102],parallel_dir:64,mypassopt:86,anymor:[86,20],llvmremovemoduleprovid:[],pointcount:82,precis:[],portabl:[],nontempl:28,bitset2:[],bitset3:[],distalwai:[],printd:[24,25,26,30,31,32,33,15,18,19],strai:13,printf:[24,25,38,93,115,108,30,31,32,33,75,96,99,5
 ,19,36,18,80],cont:[120,36,61],ymin:[18,32],short_enum:36,describ:[],would:[],gcstrategi:82,addincom:[24,25,31,32,33],llvm_doxygen_qhp_cust_filter_nam:72,initializealltargetmc:24,autogen:42,musl:[42,47],include_directori:72,must:[],llvmdummycodegen:66,"__sync_fetch_and_xor_n":53,join:[86,36,20,90],getnumoperand:20,"0x4db504":42,image_file_machine_mipsfpu:121,runfunct:[20,109],norm:[46,0,128],localrecov:[],"__data":36,int_of_float:[18,19],virtreg2indexfunctor:94,inadvis:114,registerehfram:[85,5],attract:[82,43],norecurs:36,makellvm:38,uselistord:36,straightforward:[94,113,66,115,29,30,31,32,33,86,15,88,16,17,18,19,20,108,23],stride:[],pipefail:2,concis:[94,28,43,101,114],hasnam:20,env:[49,51],frameless:94,subproject:[38,47,43,104,56],getcompilecallback:[5,6],collaps:36,dialect:[45,36],memorydependencyanalysi:53,mess:[38,48],befor:[],getnextnod:[],getreservedreg:66,mesa:47,const_iter:20,parallel:[38,94,72,2,71,126,36],bootstrap:[],exclud:[7,94,43,41,78,36],parserclass:28,includedir:11
 2,environ:[],incorpor:[94,20,113],enter:[38,94,72,119,36,111,2,30,115,93,9,124,120,16,20,22,63],exclus:[40,28,94,53,123,36],hasexternallinkag:20,frontend:[],wavefront_sgpr_count:39,over:[],commasepar:28,imul:94,blatent:[19,33],optional_dir:64,str_offset:115,modref:[128,53,58],parseparenexpr:[24,25,111,29,30,31,32,33],align32bit:124,imm:[45,94,66,128],baseinstrinfo:34,image_sym_type_dword:121,tramp:36,replaceinstwithinst:20,getorinsertfunct:20,fadd:[],comprehens:[],runtimedyldelf:85,instrprof:36,llvmbc:124,settruncstoreact:66,cfgsimplifi:20,getlazyresolverfunct:66,flaground:76,const_global_iter:20,choic:[103,38,57,101,119,27,42,26,31,52,97,87,15,36,40,17,20,62],cmake_cxx_flags_releas:38,alex:80,exampletest:2,modrefresult:58,each:[],use_begin:[101,20],complet:[48,101,0,76,50,2,77,104,105,96,111,4,5,6,59,62,9,85,56,94,11,36,115,13,81,16,17,18,19,21,22,23,24,25,84,66,82,27,28,29,30,31,32,33,86,70,71,72,40,120,42,58,43,124,41,98,99,128],prohibit:[99,53],abbrevwidth:124,setsubprogram:25,g
 prc:94,ptrtoreplacedint:20,tag_pointer_typ:115,goe:[25,94,72,66,11,82,36,42,73,53,33,63,120,76,45,19,20,108,115],llvm_optimized_tablegen:[38,72],newli:[25,48,38,59,29,30,31,32,62,75,40,16,17,5,6,20,18,9,23],laid:[16,36,94,20,88],adjust:[],rs2:66,got:[],unimagin:40,worthwhil:20,precaut:20,threadidx:[14,11],free:[101,0,102,40,26,104,54,59,9,117,58,13,15,63,16,20,21,23,82,27,29,30,31,32,33,86,71,119,42,94,53,47],getfilenam:[25,115],rangelist:46,objectlinkinglay:[5,6,59,62,9],"0x580be3":42,precompil:11,sandylak:24,puzzl:73,astdump:34,r9d:8,r9b:8,openssl:42,filter:[],addrspac:[40,120,36,11],rais:[48,82,36,93,120,40,16,17,18,19,20,21,22,23],"0x0000000000000002":109,r9w:8,onto:[38,123,82,36,94,115,104,43,50,20],rand:42,rang:[],becaus:[100,48,101,88,1,50,51,26,104,96,111,78,4,7,8,80,107,58,113,59,115,108,12,61,62,14,123,15,63,81,16,17,18,19,20,21,22,23,24,25,2,66,114,82,27,28,29,30,31,32,33,86,37,36,68,120,38,119,85,93,42,94,53,76,43,97,124,125,40,99,47,128],xnorrr:66,dw_apple_property_clas
 s:115,wordsiz:82,rank:48,restrict:[],datastructur:20,alreadi:[101,0,76,50,96,5,36,8,9,57,94,58,113,115,61,62,13,81,16,17,18,19,20,21,64,23,24,25,66,82,27,28,29,30,31,32,33,86,38,72,40,47,73,95,43,97,127],hackabl:[27,21],createcfgsimplificationpass:[25,30,31,32,33,5,6,59,62],consecut:[88,1,7,115,86,54,123,36,46],primari:[102,36,56,58,81,16,17,18,19,20,21,22,23,24,25,82,27,111,29,30,31,32,33,120,42,94,43],rewritten:94,nomenclatur:125,top:[],cstring:5,seq_cst:[36,53],tot:40,downsid:20,tok:[25,36],ton:[27,21],too:[100,101,76,50,26,52,96,4,36,62,13,15,19,93,111,22,25,28,33,86,38,20,42,94,75,43,125,128],tom:76,toolset:72,corpus:[],dw_apple_property_nul:115,initialize_native_target:[16,17,18,19],targettripl:24,consol:[16,56,94,30,127],tool:[],usesmetadata:82,xuetian:14,"__sync_fetch_and_nand_n":53,conserv:[101,58,82,40,53,104,86,99,97,36,70],llvmremoveattribut:47,dw_tag_gnu_template_template_param:36,reinterpret_cast:5,target_compile_definit:81,atomtyp:115,initsynclibcal:53,"__atomic_excha
 ng":53,fashion:[36,57,35,66],ran:[86,105],ram:[126,42],raw:[80,85,10,84,106,92,103,28,29,105,34,68,45,94,51],lbd:65,further:[],unreloc:40,rax:[66,40,94,97,83,36,8],word64:94,adc32mi:8,unresolv:[26,2,15],thorough:101,sk_somewhatspecialsquar:113,xfail:[13,51,2],expr0lh:80,thoroughli:[17,47,31],has_jit:44,atom_count0:115,interproceedur:62,though:[48,101,50,51,96,36,9,57,115,13,63,16,19,20,111,22,23,25,113,114,82,28,29,31,33,86,70,120,42,94,53,99],visitfab:57,sizeclassalloc:54,glob:10,"__apple_typ":115,bss:90,sethi:66,bsd:[38,37,43,107],"16bit":24,"0x00000002":115,failure_ord:53,"0x00000000":115,"0x00000004":115,v8p0f64:36,excis:36,flow:[],roots_begin:82,getorcreatefoo:20,declas:[],declar:[],radix:[94,37,101],pred_begin:20,shouldexpandatomicstoreinir:53,cumoduleloaddata:11,"0x70b298":86,random:[],radiu:113,smallvectorhead:20,popq:[40,97],pkg:51,radic:94,dfapacket:[],lit_config:2,absolut:[],package_str:72,bitcoderead:57,resolverti:36,cxx_fast_tl:36,nextprec:[24,25,111,29,30,31,32,33],mul
 ticlassid:46,getreg:[94,66],llvm_yaml_is_sequence_vector:76,label0:36,twiddl:[30,31,32,33,16,17,18,19,36],watch:[43,101],image_scn_type_no_pad:121,pointertyp:20,report:[],rl247422:42,rl247420:42,jitcompilecallbackmanag:[5,6,59],woff2:42,sparclet:66,aliasanalysisdebugg:58,twice:[38,49,50,30,86,96,36,125,16,20],sunit:94,isoper:[24,25,32,33],basicblock:[],stringwithcstr:115,lto_module_is_object_file_for_target:99,irgenandtakeownership:[5,6],out_of_bound:81,memory_order_releas:[36,53],storesdnod:66,richer:97,nul:[18,20,32],num:[82,40,36,66],libsampl:64,corrupt:[107,120,42,26,54,15],dumpattr:34,hopefulli:[],databas:[26,15,76],image_file_machine_mips16:121,valb:11,tolmach94:82,mul:[],approach:[],weak:[124,50,53,33,99,63,36,37,19,20],protect:[101,0,66,42,94,53,124,4,36],blocknam:124,fault:[],lgkmcnt:39,r7xx:117,"4gib":35,mybarflag:76,lto_module_cr:99,gendfapacket:94,callseq_end:40,coldcc:[40,36,124],test_suite_host_cc:51,max_int_bit:20,trust:[43,101],nake:[36,124],xemac:38,nonsens:[19,127,
 33],been:[48,101,0,76,49,50,26,53,54,55,4,5,6,7,8,9,85,57,107,11,36,115,108,62,14,15,63,81,16,17,18,20,111,22,23,24,25,2,84,109,66,114,82,28,29,30,31,32,33,86,88,128,104,38,41,72,119,40,93,42,94,96,43,97,64,120,127,46,47,110],accumul:[48,1,42,16,17,18,19,22,23],fnloc:25,oldbind:[24,25,19,33],quickli:[],getsymbolt:20,"0x000003bd":115,msec:1,xxx:[51,101,7,66],uncommon:[120,36,81],kw1:42,expected_v:36,kw3:42,vulcan:47,"catch":[],upcast:113,image_sym_class_undefined_stat:121,simplevalu:46,timeit:51,basic_p:128,basic_r:128,lesser:88,weren:43,curvar:[24,25,19,33],cumemalloc:11,binoprh:[24,25,111,29,30,31,32,33,16,17,18,19,22,23],cdecl:36,p_reg:94,image_sym_type_mo:121,svr4:107,vk_argument:101,exterior:40,registermypass:86,tediou:76,list_property_nam:44,suggest:[86,38,101,119,58,36,110,12,74,43,63,40,20,8,64],armasmprint:34,complex:[],disableencod:8,dooneiter:93,sk_lastsquar:113,asan_opt:42,sched:[90,94,66],ind4:36,darwin9:7,social:102,apr1:43,xyzzi:101,binaryexprast:[24,25,111,29,30,31,32
 ,33],build_ret:[16,17,18,19,23],"0x08":115,introductori:56,property_nam:44,redefin:[128,29,32,33,18,19,23],sethiddenflag:28,image_scn_mem_not_pag:121,bugzilla:[56,49,40,42,104,13,43,47],shortli:25,memarg:61,everyth:[52,104,96,111,36,62,56,11,12,13,81,17,18,21,22,23,114,27,28,29,31,32,86,38,94,53,75],spencer:4,addend:[94,36],makevehicl:101,setcurrentdebugloc:25,finalizememori:85,createreassociatepass:[30,31,32,33,5,6,59,62],meta:[82,20,47,94,115,97,36,8],numliveout:97,shorthand:128,lambdaresolv:[5,6,59,62,9],"0x03":97,eli:14,expos:[],interfer:[120,36,63,114],patchpoint:[],r_amdgpu_gotpcrel:94,elf:[],"0x7fffffffe018":109,els:[],at_artifici:115,explanatori:[51,43],elt:36,gave:[50,59],xnor:66,setloadxact:66,disposit:43,x0abar:42,howtosubmitabug:38,atomic_swap:53,"______________________":20,xmin:[18,32],thumb2:[117,94,36,68],thumb1:[117,47,36],gr64:94,end_:[17,18,19],apart:[72,20,88,58],colour:102,unindex:66,arbitrari:[101,40,26,111,36,58,114,15,16,19,20,21,22,23,2,66,67,82,27,28,29,30,1
 15,33,86,120,94,43,97,124,44,128],loadlal:36,contradict:43,dynamiclibrari:[5,6,59,62,9],build_add:[16,17,18,19,23],unstabl:[49,52],entry_block:19,hung:20,ifexprast:[24,25,31,32,33,17],scopelin:[25,36,115],llvm_use_sanit:72,excerpt:11,"000000e":[29,30,31,33,16,17,19,23],enumcas:76,indirect:[],successfulli:[58,1,40,73,12,32,104,120,126,98,18],live_end:82,"0x401000":89,icc:[38,115,1],attrparsedattrimpl:34,guaranteedtailcallopt:36,armv5:53,armv7:[38,117,12,52,104,88,36],armv6:[117,52],armv8:[47,117,8],registerclass:[94,34,8,66],icu:42,core:[],clase:20,tour:[111,22],subtmp:[24,25,29,30,31,32,33,16,17,18,19,23],new_corpus_dir:42,cast210:36,"0x2":[97,94,20],meyer:101,chapter:[],min_int_bit:20,canreserveresourc:94,surround:[48,114,36,53,97,7,8],unfortun:[101,50,47,26,30,31,61,86,15,36,16,17,20],distinct:[48,94,124,114,58,7,42,29,115,13,120,36,40,44,20,23],g_inlined_into_f:89,algo:86,bitsetcas:76,approxim:[3,14,2,42,96],produc:[48,101,88,1,50,2,55,4,59,62,9,80,94,7,115,60,12,61,15,40,16,17,1
 9,20,108,23,25,84,66,114,82,87,29,30,31,33,86,34,36,107,38,41,72,93,42,73,53,76,75,43,120,44,45,47],addpsrr:128,ppa:38,"_zts1a":123,"_zts1c":123,"_zts1b":123,instcombin:[],regist:[],heffernan:14,encod:[],othervt:66,unwelcom:102,parse_bin_rh:[16,17,18,19,22,23],functionproto:[24,25,30,31,32,33],createfmul:[24,25,29,30,31,32,33],objectso:[],storag:[],addpsrm:128,git:[],frustrat:102,closur:[44,26,15],readattribut:34,stuck:[26,15],"0x7":94,gid:107,image_sym_type_enum:121,"__sync_lock_test_and_set_n":53,hassideeffect:8,synthesis:[],head:[38,101,82,36,125,127,46,128],medium:[90,36],heal:100,unconvinc:42,modulepass:[],p0i32:7,add_definit:72,heap:[],icmp:[],n2541:101,counsel:43,attr:[34,36,115,124],lsan:[],symbolresolv:[62,9],pugixml:42,fundament:[],autoconf:[72,47,108,52,104,81,20],clang_enable_bootstrap:125,loadregfromstackslot:[94,66],adorn:[127,36],uncoop:82,logerror:[24,25,111,29,30,31,32,33],trig:66,eieio:36,"_ztv3bar":7,bore:86,readonli:[48,40,115,97,63,124,36],tirefactori:101,instrp
 rof_:36,add_execut:[72,81],when:[],tii:94,tid:11,d17567:47,pseudonym:0,node:[],v_mul_i32_i24_e64:39,uint8:[100,97],consid:[],idx3:114,cooper:[82,75],idx1:[36,114],src:[112,72,66,49,42,94,104,36,51,64],uniformli:101,"0x0f":97,libcuda:11,faster:[38,101,107,50,47,52,93,14,36,120,126,20,42,115],bullet:[108,113],freebench:51,seciton:35,backward:[],impli:[66,58,82,46,94,14,43,97,36,120,89,4,114,20],rob:14,focus:[94,66,82,40,60,13,20],catagor:48,movabsq:[97,95],signific:[57,101,124,88,58,40,27,42,31,32,86,82,43,99,36,50,18,20,21],parent_scop:81,computation:71,llc:[],setindexedstoreact:66,n32:[47,36],lld:[116,38,47,101,72],addregisterclass:[94,66],readabl:[],d18562:47,getorcreatetypearrai:25,pop_back:[25,28,20],sourc:[],t1item:50,feasibl:[36,115],cool:[24,25,28,29,30,31,32,33,86,16,17,18,19,23],cuctxcreat:11,curop:66,"__cdecl":36,level:[],link_modul:[],quick:[],release_26:38,release_27:38,release_24:38,release_25:38,"__builtin_longjmp":120,release_23:38,release_20:38,release_21:38,release_2
 8:38,release_29:38,hsa:[94,39],magnif:[27,18,21,32],endcond:[24,25,31,32,33,19],port:[38,94,1,47,26,15,126,4,5,108],llvmlib:64,repli:43,"64bit":[49,36],exitcond:36,sgi:20,alphajitinfo:66,cmp0054:81,eckel:20,u32:[94,11],llvmld:[],negeightkind:36,scudo_opt:54,declare_funct:[16,17,18,19,23],fmax:36,memory_order_relax:[36,53],testsut:[],rl247405:42,fmag:107,dw_tag_restrict_typ:[36,115],cmakeparseargu:81,preorder:113,zerocont:54,errorinfo:20,createbasicaliasanalysispass:[25,30],writethunk:50,switchsect:[82,94],preserve_allcc:[36,124],r6xx:117,add_librari:72,overriden:[],dorit:1,weird:94,automaton:[94,34],machine_version_minor:39,semant:[],inlinedat:[36,7],builder_at:19,globallayoutbuild:123,tweak:[38,113,28,30,74,14],visibl:[],memori:[],camlp4of:[16,17,18,19,22,23],pred:[11,36,31,33,120,17,19,20],preg:[42,94],pref:[36,20],todai:[40,101,97,53,114],handler:[100,20,94,53,120,36],upheld:40,instalia:94,diflagvector:36,msg:[36,20],andw:7,prev:20,msb:94,reorder:[36,115,7,53,40],newptr:36,plug:[
 29,23],capit:[43,101],p0v2f64:36,drown:51,prototyp:[],build_br:[17,18,19],registerinfo:[],function_typ:[16,17,18,19,23],purpos:[48,101,110,49,50,54,4,36,8,9,11,63,40,20,25,114,28,29,86,34,88,38,120,94,43],image_file_executable_imag:121,stream:[101,1,103,36,80,10,106,7,16,17,18,19,20,21,22,23,66,83,111,84,57,115,86,37,38,92,42,94,76,124,41],sidelength:113,parse_binary_preced:[18,19],backslash:42,add8rr:94,critic:[],gettyp:[101,20],alwai:[],differenti:[44,4,35,119],localescap:[],stepval:[24,25,31,32,33],twoargfp:128,anyon:[0,66,115,53,43,81],fourth:[66,28,115,86,97,17,36],cstptr:36,"__nv_isinff":11,testfunc:[16,30],no_switch:1,xzr:36,clone:[38,42,2,33,86,75,34,19,20,111],mcdisassembl:94,r_amdgpu_rel64:94,"4th":94,netinet:5,shared_ptr:[5,6],geforc:11,testresult:56,colfield:78,practic:[],firstlett:109,calltmp6:[19,33],predic:[],the_fpm:[16,17,18,19],cse:[16,57,71,30,53],destmodul:[],postrapseudo:83,combin:[],practis:70,nextindvar:36,sphinx_execut:72,"_zts1d":123,blocker:49,ymmv:101,size
 _t:[82,42,76,99,53],mainli:[50,14,34,36,64],canari:36,fsanit:42,foo_dtor:61,gte:36,branch_weight:[3,70],passag:101,gvnhoist:47,pinsrd:7,platform:[],gtu:11,symbolresolverptrt:62,getsymboladdress:[5,62,63],ymm0:97,underneath:[13,38,64],maskedbitsetcas:76,flagspointi:76,inoperandlist:[8,66],term:[48,101,102,50,4,36,62,56,58,108,13,40,82,83,115,88,71,119,120,94,53,43,97,46,128],amdgcn:94,name:[],getoperatornam:[24,25,32,33],realist:[82,111,22,128],selectcod:66,r_amdgpu_abs32_hi:94,varexprast:[24,25,33],the_execution_engin:[16,17,18,19],individu:[],otherspecialsquar:113,const0:124,getdoubleti:[24,25,29,30,31,32,33],x86call:128,mnan:[],profit:[100,48,1,94,14,63],decimalinteg:46,profil:[],sctx:42,roundp:1,iscxxclass:115,factori:[48,101,20],aliase:[50,36,124],unfriendli:42,numberofcpucor:42,"\u03c6":36,migrat:[82,43],write_escap:86,hd2xxx:94,integertyp:20,theori:[50,26,15,76],getvalueid:50,"_r0h":120,boehm:82,cmake_parse_argu:81,synchron:[99,36,53],refus:[38,10,72,92,48,103,84,106,9],motion
 :[],turn:[],place:[48,101,120,1,49,50,26,111,36,8,83,80,57,107,62,13,15,63,40,16,18,19,20,21,64,23,2,66,114,82,27,28,29,30,115,32,33,86,126,88,90,38,119,39,93,47,94,76,75,43,97,125,44,128],ture:[16,111,30,22],imposs:[66,58,26,53,43,15,88,9],str1:128,origin:[0,102,40,105,4,36,62,9,107,7,67,8,43,110,20,25,114,115,38,120,94,123],suspend:82,sanitize_memori:36,toruntimedyldsymbol:[5,6,59,62,9],dw_apple_property_copi:115,arrai:[],bou_fals:28,dllvm_external_foo_source_dir:72,predefin:[86,94,18,2,32],unrecogn:28,"0x00003550":115,given:[48,101,76,40,2,105,96,111,55,4,5,6,59,62,9,85,57,107,58,113,36,60,63,81,18,20,108,22,23,84,66,67,28,29,30,115,32,86,34,89,70,38,72,119,120,94,53,122,75,123,97,124,44,46,128],frameindex:66,gif:42,image_sym_class_external_def:121,associ:[48,101,50,54,3,4,36,80,107,81,20,111,22,85,66,82,28,30,87,35,88,68,70,71,40,120,47,94,123,97,124,44,128],reli:[101,1,49,40,36,9,108,13,63,81,19,20,114,82,115,33,88,70,42,94,43,99],assort:25,necessarili:[25,101,114,38,49,40,108,
 115,90,36],circl:113,white:117,alac:51,cope:[28,20],exitonerr:5,copi:[],specifi:[],image_scn_mem_execut:121,enclos:[101,7,13,97,124,89,20,128],pragma:[],grunt:28,releasei:49,serv:[48,0,114,56,46,2,115,13,97,88,120,5,6,20],wide:[102,26,52,53,36,56,11,15,81,16,17,20,114,82,30,31,115,38,47,94,58,124,46,128],image_sym_type_doubl:121,subexpress:[71,58,111,30,31,32,33,86,16,17,18,19,22],getoperationnam:57,posix:[37,72,107],balanc:[43,53,125],posit:[],int16_t:[76,66],xxxgenasmwrit:66,codegen:[],seri:[],pre:[],pro:88,image_sym_class_enum_tag:121,isfunct:115,subroutin:[82,36],doiniti:[],django:[0,102],bitwis:[],llvm_create_xcode_toolchain:72,techniqu:[1,50,36,58,16,17,18,19,93,21,22,66,82,27,111,30,31,32,33,86,20,94],moreov:[48,94,36],codegen_proto:[16,17,18,19,23],ideal:[101,66,40,42,44,20],sure:[101,1,49,94,52,104,105,96,4,8,57,58,41,115,108,12,13,15,63,110,19,20,111,23,24,25,113,28,29,30,31,32,33,86,88,38,72,119,73,53,74,75,43,126],multipli:[48,57,71,36,94,122,14,20,70],"__asan_memcpi":42
 ,clearer:101,fca:71,nproc:38,llvm_build_llvm_dylib:[38,72],gunzip:[38,96],icon:119,bb0_30:11,adopt:[4,43,101,94,9],quantiti:36,mybison:51,cortex:[47,12,52,68],readjust:94,"0x90":40,xxxasmprint:66,image_sym_class_end_of_funct:121,cmakelist:[38,81,72,66,67],apple_namespac:115,build_cal:[16,17,18,19,23],uncondit:[48,66,40,94,31,105,17,18,19,36],cheat:59,painlessli:28,recombin:9,permiss:[85,38,0,107,43,126,9],culinkst:11,"__global__":14,explicitli:[48,101,1,40,51,26,7,85,58,36,108,61,15,63,20,23,114,82,83,28,29,38,72,119,42,94,125,128],lua:82,derivedtyp:[57,29,30,31,32,33,20],state:[],sk_circl:113,buildmodul:9,abs_fp32:8,analys:[38,57,94,58,56,84,115,86,36,48,20,70],llvm_scalar_opt:[16,17,18,19],mcsectionmacho:94,viewpoint:102,yaxxz:120,motohiro:94,ssp:[36,115,124],allocat:[94,36,66],ssl:42,dyn:69,tailor:52,image_comdat_select_largest:36,operand_type_list_end:66,sse:[24,66,94,54,68,36],regtyp:66,dw_tag_packed_typ:115,reveal:114,"0x00002023":115,dramat:[38,101,28,30,87,16,36],intrins:[],
 irrespect:72,fastcc:[94,36,108,124],indirectstubmanag:[6,59],bison:51,scott:101,backedg:[48,40,31,32,17,18,70],drawback:[43,28,6,20,81],n16:11,rmw:53,lnt:[13,49,51,12],ilist_iter:[],maximum:[72,58,50,28,94,53,70,36,55,20,42],labori:20,atomic_:53,detect:[],hexadecom:37,review:[],get_register_match:34,cxx_fast_tlscc:[36,124],image_scn_cnt_uninitialized_data:121,abs_f:8,cycl:[99,36,115,120],isatleastacquir:[],collect2:75,come:[101,102,76,50,26,105,78,59,9,57,107,11,36,115,61,13,15,81,16,17,19,20,21,64,23,114,82,27,29,30,31,33,86,38,72,94,43,124,41,128],latch:36,at_apple_runtime_class:115,region:[],quiet:[28,2,36,109],contract:[],nocaptur:[48,36,124],mapopt:76,image_scn_mem_purg:121,imgrel:35,image_file_machine_powerpcfp:121,nnn:107,color:[105,94,20],rescan:50,inspir:[48,36,115],period:[82,93,42,13,43,36],pop:[24,25,82,36,94,31,33,124,125,17,19,20],hblcnsviw:28,image_file_machine_sh4:121,image_file_machine_sh5:121,colon:[72,76,13,81,44,7,128],image_file_machine_sh3:121,pod:101,poll:[82,
 40],spcc:66,coupl:[25,99,119,36,26,31,32,53,86,43,15,63,17,18,20,128],pend:[24,25,109,38,111,29,30,31,32,33,9,16,17,18,19,22,23],test_source_root:2,sectionnumb:121,debug_str:[7,115],hexinteg:46,savesomewher:101,variableexprast:[24,25,111,29,30,31,32,33],mytype1:76,andrew:82,mytype2:76,mrmdestmem:66,compactli:128,spirit:102,"case":[],addimm:94,subtool:14,amend:119,mount:38,registerwithsubreg:66,dw_apple_property_weak:115,cast:[],tblgen:[],"__atomic_load_n":53,exportedsymbolsonli:62,dcmake_c_flag:52,anytim:[],emittrailingf:53,isextern:115,clutter:43,image_file_up_system_onli:121,rangepiec:46,loophead:[36,31,32],d15:66,addedcomplex:8,value_desc:28,d10:66,d11:66,d12:[123,66],author:[],alphabet:[],ubsan:42,trip:[],html:[38,57,101,72,49,42,12,104,105,34,117,51],intreg:[78,66],eventu:[48,113,36,42,31,61,120,40,17,7,51,9],llvmlibthin:116,hasadsizeprefix:8,week:[43,0],image_sym_class_label:121,see:[],nest:[],confidenti:[43,0],driver:[],director:43,devoid:94,viewgraph:20,moder:[20,101,0,119],
 supporttest:72,justifi:[99,107],iterat:20,without:[],model:[],unimpl:86,tip:[],"0x000003f3":115,violent:102,redwin:94,kill:[86,83,94,93,41],xxxbranchselector:66,dynamic_cast:[24,25,101,113,33,20],blow:42,miscellan:[],widest:43,hint:[],except:[],blog:47,cxx:[49,38,12,75],blob:[49,124],notori:4,vulner:54,disrupt:127,cudadevicereset:14,processrelocationref:85,predrel:78,subtargetfeatur:[47,8,66],createbr:[24,25,31,32,33],predreg:78,tie:36,"0x000003ff":94,earlycs:63,"0x1000":115,whitespac:[24,25,101,38,46,27,111,29,30,31,32,33,43,16,17,18,19,7,21,22,23],image_scn_align_256byt:121,tend:[100,38,101,114,49,60,115,43,44,20],evergreen:117,at_apple_property_attribut:115,critedge1:11,libsfgcc1:12,slice:[46,20,128],"__atomic_fetch_nand_n":53,easili:[24,38,73,48,40,59,28,67,115,86,76,13,82,101,97,63,50,44,4,94,20],benefici:1,legal:[],gridsizex:11,encodecompactunwindregisterswithoutfram:94,gridsizez:11,derferenc:[],freea:61,complic:[38,57,101,72,113,66,1,82,120,42,125,61,53,13,96,123,81,36],freed
 :[95,20,62,9,58],llvm_doxygen_svg:72,garbag:[],inspect:[],boolordefault:28,bpf_mul:94,debug_with_typ:20,microcontrol:117,immut:[86,36,20,68],execv:4,craft:20,mergabl:48,cmptmp:[24,25,29,30,31,32,33,16,17,18,19,23],stanc:101,stand:[86,101,20,111,94,13,43,36,5,6,59,62,22],image_scn_align_16byt:121,onon:36,routin:[],llvmsetdisasmopt:45,dw_at_nam:[7,115],tbcc:66,lastli:[13,25,86,68],overrod:128,idx2:114,cpu_powerpc:76,myregalloc:86,unconvent:[26,15],idx0:36,classess:66,baeslayert:62,fcc_g:66,getbuff:76,strict:[110,7,29,115,63,88,50,44,20,8,23],racist:102,v_mul_i32_i24:39,mm4:[8,128],tracksregl:83,subtargethook:[],strictli:[24,38,11,40,7,29,31,115,120,36,17,4,20,9],blocklen_32:124,machin:[],arg_end:20,setfoo:36,mm6:[8,128],tupl:36,regard:[56,101,108,61,53,34,104,36],ocaml_lib:[16,17,18,19,23],amongst:53,ffi_include_dir:72,setjmp_buf:120,procedur:[71,117,88,27,47,21,3,63,36,50,104,20,28,64],r_amdgpu_abs64:94,getdata:101,longer:[48,101,36,62,107,108,63,19,20,64,82,30,33,86,68,42,94,53,122,
 43,127,47],notat:[],nmake:72,parsetoplevelexpr:[24,25,111,29,30,31,32,33],handletoplevelexpress:[24,25,111,29,30,31,32,33],make_uniqu:[24,25,111,29,30,31,32,33,5,6,59,62,9],compute_factori:109,x86_stdcall:94,primarli:83,dllvm_external_bar_source_dir:72,clrq:94,clrw:94,cbe:73,frighten:42,strongli:[71,82,47,26,12,31,33,101,15,63,81,17,19,128],clrb:94,intro:[56,19,117,33],enginebuild:[85,5,6,59,62,9],umax:36,print_list:81,rearrang:71,jitfuncid:5,tok_eof:[24,25,27,111,29,30,31,32,33],clrl:94,incorrect:[],new_potentially_interesting_inputs_dir:42,idiom:[28,29,20,23],"0xabcdef00":40,symbol:[],briefli:[80,50,86],mrmsrcreg:66,lexicalblock:25,llvmcreatedisasm:45,serious:96,buildmi:94,llvm_include_exampl:72,callq:[40,95,97],directori:[],invest:57,calle:[],defaultlib:96,degrad:82,rabfik:107,"0xl":36,metatada:3,all:[],replacealluseswith:[50,71,20],dist:[],fp_to_sint:66,lack:[102,114,82,36,94,74,14,110,16,46,8,128],scalar:[],basicblockutil:20,print_final_stat:42,abil:[76,102,36,57,115,109,63,17,
 18,19,20,21,64,82,27,28,84,31,32,33,47,94,45],ptx:[],follow:[],changebit:42,disk:[38,101,99,42,2,115,44,4,36,9],ptr:[],uint8_t:[5,76,42],doe:[],targetdescript:66,getaddressingmod:66,init:[],program:[],mayfail:20,neglig:[100,42],liter:[100,101,111,36,83,107,81,16,17,18,19,20,21,22,23,24,25,27,28,29,30,31,32,33,76,124,45,46,128],lsbit:20,far:[57,29,58,59,28,26,115,32,33,86,15,36,81,44,18,19,20,111,22,23],urem:[],getbasicblock:94,novel:[82,36,20],worst:[20,26,15,95,40],toolbuildpath:[],failur:[86,38,73,51,76,49,7,42,2,52,93,13,96,43,36,41,104,20,21,22,115],unoffici:114,mips64r6:47,experimental_dir:[],induct:[],basicaliasanalysi:[86,25,58,48],lisp:[82,26,15],sectionnam:124,list:[],lli:[],"_zst1a":123,snapshot:58,dox:102,ten:114,use_llvm_analysi:[16,17,18,19,23],tee:93,hashdata:115,rate:[43,107,124,55],pressur:[94,101,1],design:[],storageclass:121,llvm_ani:57,hasard:82,subobject:123,attrdump:34,what:[],namedindex:66,handler0:36,handler1:36,handler2:36,sun:[13,86],sum:[1,20,105,124,36,70]
 ,brief:[38,101,72,58,82,50,28,73,81],overload:[57,113,66,11,36,32,86,40,18,20],asmprint:[82,94,34,66],version:[],intersect:101,llvmgetbitcodemodul:47,row:78,themselv:[94,124,50,28,2,53,115,43,111,36,44,20,8,22],memorybuff:101,xmm3:[36,8,128],xmm0:[13,97,7,8,128],xmm1:[8,128],themself:43,roots_iter:82,solari:38,xmm5:[8,128],build_config:96,goodby:127,xmm9:8,asmpars:[38,57,34],misinterpret:[101,93],quarantinesizemb:54,deregisterehfram:5,instrsdrm:128,observ:[101,40,47,26,53,15,94,36],llvm_profdata_fil:[72,125],xmm2:[36,8,128],magnitud:36,"0x0000006e":115,deprec:[72,47,20,52,124],heurist:[48,19,36,94,33],customiz:14,sparcasmprint:[94,66],dump_modul:[16,17,18,19,23],hexadecim:[],proceed:[82,38,14,94],normalizedpolar:76,coverag:[],upstream:[38,14,63],qch:72,forcefulli:114,llvmtargetmachin:66,llvmaddtargetdependentfunctionattr:47,cxa_demangl:115,isload:94,"80x86":126,customis:72,flag:[],stick:[101,20,52],"0x00000067":115,known:[],ensu:[66,125],valuabl:[51,43],"_e64":39,outlin:[86,94,43,12
 0,76],portugues:54,faultingpcoffset:100,cmake_:81,relocationtyp:66,dmpqrtx:107,debug_abbrev:98,image_scn_align_8192byt:121,ppc64:[47,94],reevalu:46,bjark:14,pong:50,bjarn:20,invokeinst:20,cours:[57,72,58,27,28,26,62,86,15,42,111,50,20,21,22],newlin:[101,124],divid:[48,57,36,51,94,13,14,55,4,7,70],rather:[48,101,102,49,40,2,52,96,59,62,9,58,36,108,13,14,63,20,22,25,66,114,82,111,29,115,70,42,94,43,124,46,47],anxiou:72,hash_map:20,divis:[18,94,36,32],value_align:36,targetasminfo:[82,66],goat:101,distro:12,resourc:[],algebra:[48,36],ranlib:[38,75],reflect:[],okai:[24,25,71,119,114,111,29,30,31,32,33,101,17,16,4,18,19,36,22,23],ptxstring:11,pr26774:47,"short":[101,76,40,2,96,36,62,80,11,108,17,18,19,25,66,31,32,33,88,89,38,94,58,43,97,118],postfix:101,unhid:28,stash:113,ambigu:[113,28,32,13,18,46,111,22],caus:[48,73,1,94,2,105,101,111,55,4,7,85,57,107,11,36,60,13,123,116,19,20,108,22,25,84,82,28,29,31,32,33,86,88,90,38,93,47,58,53,76,75,43,64,41,42],callback:[66,58,82,20,94,97,59,9],pre
 pass:94,llvmgetdatalayout:47,fslp:1,gprof:[],hton:5,reachabl:[82,36,71,72,40],s_load_dwordx2:39,geomean:1,next_var:[17,18,19],dso_path:87,typedef:[101,20,76,5,6,59,62,9],exyno:47,lai:[25,71,114,123,36,94,33,101,16,17,18,19,20],d31:36,resort:120,anachronist:124,retti:124,might:[101,102,76,50,26,53,54,3,4,7,107,58,113,36,108,12,15,63,40,17,18,19,20,64,24,2,66,82,28,110,31,115,34,104,38,71,72,119,93,42,94,96,43,44,45,127],alter:[86,36,28,20],wouldn:[25,19,101,33],"return":[],success_ord:53,setgraphattr:20,var_nam:[17,18,19,81],framework:[48,57,94,56,82,27,51,29,58,32,33,86,115,36,18,19,20,21,23],preheaderbb:[31,32],somebodi:[43,62],bigger:[101,76],strr:66,complexpattern:[94,66],sourcebas:56,blockdim:11,runhelp:101,refresh:99,const_float:[16,17,18,19,23],hasjit:66,remotejitutil:5,truncat:[47,36,66,128],compriz:55,dcmake_cxx_compil:42,"2x3x4":36,colder:70,compute_20:11,linkag:[],regmapping_f:94,asmparsernum:118,expect:[],atom_count:115,constindex:97,fdrpcchannel:5,resulttyp:36,foolproof:
 86,ccifinreg:66,lineno:25,image_file_line_nums_strip:121,benjamin:82,isempti:20,uncommit:38,compilecommonopt:[],"0xxxxxxxxx":115,teach:[57,27,29,21,9,23],pre_stor:94,flagflat:76,thrown:[100,120,36],targetinfo:[43,66],putchar:[24,25,30,31,32,33,16,17,18,19],thread:[],vararg:[94,20,29,124,36,23],toolnam:64,perhap:[101,58,82,50,36,20],machineframeinfo:94,ccifnotvararg:66,threat:[0,102],precal:82,libclc:43,feed:[58,42,115,31,125,17],notifi:[104,43,0,58,1],ystep:[18,32],feel:[29,0,102,27,47,26,101,93,43,15,63,36,21,23],cuda_success:11,add16mi8:8,isunpredicatedtermin:66,summaris:88,cond_val:[17,18,19],construct:[],stdlib:38,blank:[101,107,119,27,111,26,43,15,127,21,22],slower:[101,82,50,94,14,63,36,120,20,108],fanci:51,gpl:[43,108],superpos:20,script:[],interact:[],gpg:38,stori:[80,38,96],gpu:[56,117,39,66,11,94,14,34,36],store:[],luckili:82,option:[],atempt:36,wswitch:101,st_gid:107,cmake_c_flag:72,inc4:7,initializealltargetinfo:24,r_amdgpu_abs32_lo:94,secondcondit:20,albeit:[19,33],kind
 :[48,101,0,102,50,3,55,36,8,9,80,57,107,108,87,123,18,19,20,24,25,113,82,83,28,115,32,33,34,68,71,120,42,94,53,43,97,44,127,99],assert_valid_funct:[16,17,18,19,23],doubli:[95,20,81],artifact_prefix:42,whenev:[41,101,58,7,28,81,125,109,13,78,97,36,27,44,20,62],remot:[85,38,6,9],remov:[],pictur:[50,29,114,23],get_subtarget_feature_nam:34,empty_subregsset:66,dinkumwar:20,cleaner:[28,101,20],body_v:19,nnan:36,peculiar:46,ysvn:104,astwrit:34,aspir:[18,32],dedic:[42,94,66,9],"0x10":[97,115],entireti:40,"0b000100":66,check:[],"64mb":54,manglednam:[5,6,59,62,9],arm_aapcscc:124,mtlo:[],paramidx1:124,paramidx0:124,belief:102,exec:[41,42],unsur:[46,0],getrawpoint:68,reach:[100,48,101,0,66,82,50,42,97,120,44,36],flagsround:76,assignvirt2phi:94,shouldexpandatomicloadinir:53,image_rel_amd64_addr32nb:35,cmakefil:[38,51],appear:[80,48,60,107,66,58,20,28,2,53,93,101,36,40,114,46,62,115],dw_tag_enumeration_typ:[36,115],xmm7:[8,128],blockid:124,destruct:[47,26,61,15,97,20,9],libopag:74,sandybridg:1,ar
 g_empti:20,rtl:94,getcol:25,intti:36,optimizationlevel:28,inapplic:52,flat_store_dword:39,brtarget:66,penalti:[36,20],"__llvm_deoptim":36,dw_apple_property_retain:115,bfd:75,create_add:23,image_file_large_address_awar:121,hash_funct:115,stackoffset:82,shlibext:13,address_s:11,blockscalartrait:76,pushfq:94,"0x0001023":115,hit:[5,6,101,42,70],invoke:36,aliasopt:28,spurious:[13,36],aliasanalysiscount:58,mydoclisttyp:76,fastest:126,sizabl:20,stdcall:[94,36],pushfl:94,him:50,exactmatch:36,llvmdummi:66,sk_otherspecialsquar:113,armhf:12,ssl_set_accept_st:42,"0x1234":115,wrote:[24,25,57,36,114],arr:[36,20,114],art:82,dump:[76,55,115,16,17,93,23,24,25,29,30,31,32,33,86,34,20,42,94,122,124,98],cleverli:88,sensit:[76,72,58,83,42,60,86],shared_librari:64,subsum:42,mutabl:[],arc:[105,119],bare:[112,66,20,97,36,9],arg:[101,50,2,105,111,36,41,109,40,16,17,18,19,21,22,23,24,25,27,28,29,30,31,32,33,90,42,73,122,46],disadvantag:[99,28,20,68],icc_:66,unqualifi:[111,94,115],arm:[],property_valu:44,setu
 pmachinefunct:66,inconveni:[42,19,33],inst_end:20,old_valu:19,maprequir:76,pubtyp:115,condv:[24,25,31,32,33],extensioan:49,syntact:[16,30,7,36],unabbrev:124,sole:[43,20],gcfunctioninfo:82,"0x000000c9":7,setbid:124,succeed:[86,2,36,70],indirectstubsmanag:[5,6],solv:[94,114,58,26,115,32,33,43,15,104,18,19],classnam:118,v128:[36,11],amd64:38,disclaim:81,interprocedur:[],portablecl:[],"__atomic_stor":53,blissfulli:28,isomorph:108,available_extern:[36,124],context:[],mthi:[],subclassref:46,internallinkag:20,tgt:118,getsrc:38,libxxx:12,sweep:82,zchf:12,arbitrarili:[113,47,31,115,17,36],mistak:[101,63,102],java:[100,48,82,36,26,53,15,20],due:[73,49,50,52,101,7,3,58,36,109,14,63,40,82,38,71,46,42,94,123,120,99,47],libomp:[49,38],stdint:42,brick:50,whoa:[16,30],strategi:[],thunk:[123,48,94,36,50],dw_tag_imported_modul:36,flight:[120,36],append_block:[16,17,18,19,23],llvm_map_components_to_librari:72,demand:[38,94,33,124,19,9],instructor:66,asmmatcheremitt:34,echocmd:[],eatomtypedietag:115,fr
 ozen:109,batch:[47,96],dagtodagisel:57,dw_tag_friend:36,abov:[100,48,101,0,88,76,49,50,51,26,111,78,5,6,7,8,9,102,85,57,94,58,113,59,115,108,12,62,13,15,63,81,16,17,18,19,20,21,22,23,25,66,114,82,27,28,29,30,31,32,33,86,36,89,70,107,38,72,40,41,42,73,95,53,123,97,64,124,83,45,127,99,128],intendend:36,cmp32ri:[],pienaar:14,runonfunct:[],image_file_machine_am33:121,rip:[13,83,36,8],floattyp:20,rid:50,illinoi:[],mioperandinfo:66,dw_lang_c:25,shirt:102,minim:[],getnumel:20,dominatortreebas:20,higher:[],x83:121,x87:36,x86:[],mytyp:36,robust:[13,45],wherev:[25,14,101,20],obit:36,lower:[],n2429:101,machineri:[51,113],discourag:[4,28,0,20],find_packag:72,emitjumptableaddress:66,searchabl:[62,9],cudamemcpyhosttodevic:14,throwawai:125,chees:101,local_unnamed_addr:[36,124],erasebyt:42,propos:[],rewound:120,stripwarnmsg:[],targets_to_build:12,succ_end:20,bpf_call:94,label_branch_weight:3,theoret:[4,20],xxxisellow:66,circumv:28,exposit:[27,21],getbinarycodeforinstr:66,lmalloc:28,filename1:80,lcu
 dart_stat:14,finder:56,view_function_cfg_onli:17,complaint:[26,15],erasefrompar:[24,25,66,29,30,31,32,33,20],int32x4_t:88,v64:[36,11],ispoint:50,mypassnam:20,v60:[],preexist:48,discriminatori:102,image_sym_class_bit_field:121,fbb:66,confront:[63,114],llvm_yaml_is_flow_sequence_vector:76,short_wchar:36,xmm10:8,collect:[],xmm12:8,xmm13:8,xmm14:8,xmm15:8,cst_code_wide_integ:124,global:[],understood:[94,101,15],litter:43,unspecifi:[39,11,40,51,94,36],consciou:[],llvmgettypekind:57,surpris:[20,26,15,36,50],condition_vari:38,multmp:[24,25,29,30,31,32,33,16,17,18,19,23],affili:81,dataflowsanit:42,socklen_t:5,henderson2002:82,proj:104,prof:[3,70],patchset:38,proc:[38,52,66],studi:[63,64],kernel_code_version_major:39,n3206:101,emitinstruct:[94,66],assignvirt2stackslot:94,runtimedyld:[85,5,6,59,62,9],lose:[86,26,15,115],mustquot:76,lhs_val:[16,17,18,19,23],llvmgetbitcodemoduleincontext:47,ispointertyp:101,"_unwind_resum":120,"3dnow":24,arg_begin:[20,33],"_ztv1d":123,"_ztv1a":123,"_ztv1b":123,
 "_ztv1c":123,"0x000034f0":115,getdatalayout:[82,25,66,33],threadid:11,tok_then:[24,25,31,32,33],plethora:[38,108,20],branchfold:66,prec:[24,25,32,33,18,19],stretch:47,operandmap:66,question:[],fast:[],adjac:[46,20,36],"__cxa_call_unexpect":120,files:79,lto_codegen_set_pic_model:99,repeatedli:[100,36],gcca:106,"0x7fffe3e864f0":42,delta:73,consist:[],confusingli:53,caller:[48,108,88,66,82,50,42,94,95,31,32,93,86,36,120,17,18,20,23],cmpnumber:50,expandatomicrmwinir:53,mflop:1,msa:36,tdrr:90,highlight:[80,25,38,94,34,63,81,127,20],worklist:[48,20,50],tooldir:[],alu32_rr:78,icc_val:66,cleargraphattr:20,phieliminationid:94,cover:[],o32:47,composit:[36,20],numconst:97,simm13:66,cciftyp:66,xmsvc:81,pat:[94,8,66],sdvalu:[94,66],remove_if:20,registerdescriptor:66,nice:[48,101,26,54,111,7,15,16,17,18,19,20,21,22,23,27,28,29,30,31,32,33,86,38,128],ecosystem:[44,20],at_decl_fil:115,storeregtostackslot:[94,66],parseprimari:[24,25,111,29,30,31,32,33,18],add64ri32:8,ccpromotetotyp:66,breviti:[88,11
 ],meaning:[114,82,20,84,34,40,90,127,36],makelight:101,ccifcc:66,dllvm_default_target_tripl:12,numeltsparam:36,ternari:94,gr1:36,elementtyp:36,gr8:[94,66],spillsiz:66,scroll:119,cmpq:95,pervert:[8,110],edg:[],edi:[83,94,7,8],numfilenam:80,block_begin:[16,17,18,19,23],gmake:[86,51],memoryssa:47,int8ti:20,edx:[94,36,8,128],modulehandl:[5,6,59,62,9],printexprresult:5,uphold:36,xxxiseldagtodag:66,else_bb:[17,18,19],vptr:[36,20],needstub:66,outgo:[36,70],attributerefer:34,formbit:8,openwal:[],fpformbit:8,templateparam:36,whichev:[115,119],w64:72,vadv:51,emitconstantpool:66,reles:52,relev:[],sk_buff:94,mandelhelp:[18,32],sk_specialsquar:113,"0x0002023":115,getnam:[24,25,108,29,30,31,32,33,86,5,6,20],maxsiz:101,loop_end_bb:[17,18,19],h_inlined_into_g:89,pleas:[101,0,102,49,40,26,52,104,96,78,36,11,12,13,15,63,81,94,20,23,65,66,82,29,126,38,91,118,72,119,42,73,53,43,125,44,127,46,47,128],smaller:[48,101,119,82,36,51,94,53,116,43,63,20],dsym:89,cfi:[83,71,120],lcuda:11,cfe:[38,14,43,119,104]
 ,hardcod:[78,66],dllvm_binutils_incdir:75,fold:[],numstr:[24,25,27,111,29,30,31,32,33],folk:[42,119],compat:[],pointer_offset:40,b13e8756b13a00cf168300179061fb4b91fefb:42,undetect:42,compar:[],mainlin:[43,104],smallconst:97,err_load_bio_str:42,dllvm_enable_doxygen_qt_help:72,proj_obj_root:64,finishassembl:82,juggl:14,demateri:[],dllvm_targets_to_build:[72,12,52],chose:[16,49],sexi:[27,21],ocamlbuild_plugin:[16,17,18,19,23],destbitcodelib:[],libltdl:[],inaccessiblemem_or_argmemonli:36,sse41:7,larger:[10,101,66,40,36,94,57,115,43,35,124,55,20],shader:[94,47,101,117],n2927:101,nsstring:115,unattend:93,typic:[100,48,101,26,104,105,96,55,36,85,107,58,113,7,13,14,15,20,64,66,114,82,83,115,86,37,71,72,92,119,120,42,94,53,97,44,45,99],n2928:101,apr:4,appli:[48,101,102,76,49,26,104,105,4,36,62,85,107,58,15,63,81,16,18,19,20,66,114,99,28,84,30,115,32,33,86,35,88,38,119,39,93,42,94,53,43,126,46,128],app:[74,101,20],inequ:94,loopcond:[24,25,31,32,33,17,18,19],api:[],duck:20,opcod:[24,25,101,113
 ,66,128,50,42,29,53,32,33,111,36,78,18,94,20,8,22,23],transformutil:44,gnuwin32:[96,72],sourcefil:105,emitconstpooladdress:66,fed:94,from:[],usb:52,ineg:94,few:[48,101,102,1,40,26,104,4,59,107,11,36,13,14,15,81,16,18,20,22,23,25,84,66,82,111,29,30,115,32,86,120,38,72,93,47,94,53,43,64,124,125,44],usr:[38,72,11,28,12,52,75,14],movsx16rr8w:94,my_addit:115,sort:[],clever:[26,15,113],ap2:36,cimag:[18,32],adc64mi8:8,llvmtooldir:[],tok_identifi:[24,25,27,111,29,30,31,32,33],is_zero_undef:36,localdynam:[36,124],dllc:13,optimizefunct:[5,6,59,62],augment:[18,20,32],"_name_":81,lbb0_2:95,corpus_dir:42,add64mi8:8,annot:[],annoi:101,no_dead_strip:36,lf_typeserver2:115,getregclass:94,proof:3,expr1lh:80,tar:[49,38,42,12,96],isindirectbranch:8,movapd:7,tag:[],proprietari:43,mips32:53,tag_apple_properti:115,serial:[38,57,56,50,76,34,83,64],jingyu:14,sit:62,featurefparmv8:8,six:[94,2,53],linaro:52,sig:38,implicitdefin:83,subdirectori:[],instead:[],constantfp:[24,25,29,30,31,32,33,20,23],sin:[],chri:
 [101,26,104,86,14,43,15,94],sil:8,tension:[19,33],msdn:[116,101],"__atomic_exchange_n":53,vehicletyp:101,hazard:[47,71],singlethread:36,printdens:[18,32],attent:[38,0,102,66,13,43,36,9],ethnic:102,hasiniti:20,xarch:38,mynewpass:41,light:[101,36],llvm_build_exampl:72,modulesett:62,elid:[82,61,128],elig:48,ouput:[],desrib:80,elim:[87,115],dw_tag_memb:[36,115],attrparsedattrlist:34,build_fsub:23,watchpoint:[],reilli:20,criterion:54,"80x87":94,in32bitmod:94,attrpchread:34,nonneg:36,guess:[72,42,30],devel:49,successor:[],nfc:71,trac:126,dbuilder:25,edit:[38,20,72,107],trap:[],instsp:66,forcibl:36,image_scn_align_8byt:121,mylistel:76,virtregmap:94,"__stack_chk_fail":36,our:[101,0,102,1,50,26,111,5,6,59,62,9,94,11,115,14,15,81,16,17,18,19,20,21,22,23,24,25,82,27,28,29,30,31,32,33,86,38,72,40,47,73,74,43,125,99],out:[],const_use_iter:20,llvm_compiler_job:72,m_func:20,distnam:[],categori:[],sectalign:28,stroustrup:20,llvmbb:56,llvmconfig:72,gettargetmachin:[25,30,31,32,33,5,6,59,62,9],dive:[
 27,21,113],excess:[90,42,87],proviso:43,test_single_input:[],powerpc:[],bitset1:[],dictionari:[],anyhow:36,promptli:43,my86_64flag:76,image_sym_class_undefined_label:121,tailcalle:94,lto:[],libcxxabi:38,optimizemodul:[5,6,59,62],isdef:94,mrm1r:66,echo:[38,127],isfoo:101,"0x2000":115,"0dev":51,prioriti:[36,0,115,114],invidu:0,unknown:[],ntohl:94,printoperand:66,boil:[113,31,32,43,88,17,18],misunderstood:[],tidbit:[],shell:[25,108,72,38,28,2,13,127,93],unabridg:[19,33],shelf:[62,9],juli:82,difwddecl:36,mantain:[],protocol:[40,101,36],lea:[94,8],svnup:38,probe:[],utf:[38,34],ssl_new:42,bitcodewrit:[57,20],clip:109,favorit:[17,71,31],cohen:4,linker:[],appel89:82,peform:88,coher:[44,36],lowerfp_to_sint:66,disjoint:[58,36,1],inform:[],diverg:[18,36,32,114],rout:58,roun:14,"__unwind_info":94,anyregcc:[97,36,124],preced:[48,101,2,54,7,9,58,36,115,16,17,18,19,20,21,22,23,24,25,67,27,111,29,30,31,32,33,37,97,46],which:[],newabbrevlen:124,createstub:[5,6],ncsa:43,sync_timeout:[],llvmtarget:64,
 clash:[36,5,6,101],endmacro:81,safepointaddress:82,compiler_rt:43,sunwspro:38,image_file_machine_ia64:121,codegen_expr:[16,17,18,19,23],why:[],"_build":[],attributelist:[34,68],dens:[36,20,124],addregfrm:66,pipe:[4,2,7],add_custom_target:81,osuosl:126,determin:[],targetgroup:44,someth:[48,101,76,50,26,96,78,4,7,57,94,58,113,36,15,40,16,17,18,19,20,111,22,23,24,25,66,28,29,30,31,32,34,37,38,119,42,73,43,125,127,46,128],const_arg_iter:20,mips64el:47,"30pm":76,mainloop:[24,25,111,29,30,31,32,33],filetyp:[24,96,87,115],arm_neon:[34,88],liveinterv:[90,94],eas:52,strtol:28,locat:[],strtod:[24,25,27,28,29,30,31,32,33,111],"__sync_synchron":53,eatomtypetypeflag:115,multmp4:[16,30],local:[],multmp1:[29,23],multmp2:[29,23],multmp3:[29,23],contribut:[48,65,56,94,86,43,63,36,40,20],pypi:[],succe:[10,118,106,107,113,120,103,111,84,92,112,33,13,87,55,126,19,7,41,22],buildtool:44,blarg:20,operating_system:36,localtarget:[],regalloclinearscan:94,image_rel_i386_sect:35,partit:[],view:[],modulo:[94,3
 6,115,39],knowledg:[80,48,101,82,26,127,13,43,15,124,45,94,36],maketir:101,objectcach:85,dw_form_xxx:115,ebp:[120,94,8],p20:11,thiscal:[],ebx:[94,35,8],gmail:[38,119],closer:[71,114],ht206167:42,entranc:36,framemap:82,synthesizedcd:88,below:[48,101,1,49,50,51,52,53,54,3,5,6,7,62,9,80,10,94,11,113,36,115,12,61,13,14,123,63,81,16,18,19,20,111,22,24,25,66,83,28,30,31,32,33,86,34,104,107,38,72,119,39,122,40,87,58,95,96,76,43,97,64,124,125,44],dll:[],favor:[47,43,51],structtyp:20,beginassembl:82,"__apple_nam":115,rppassmanag:86,image_sym_dtype_funct:121,disttargzip:[],amen:94,cudamodul:11,sprinkl:20,job:[72,113,42,86,4,62],entir:[48,73,1,40,51,26,105,101,55,7,107,11,36,13,15,63,16,94,20,23,2,66,114,82,28,29,30,115,86,88,38,42,58,53,76,43,124,44],noalia:[],externallinkag:[24,25,29,30,31,32,33,23],exclam:36,swift:[47,36],addit:[],"0x00000120":115,thenbb:[24,25,31,32,33,17],constantint:[101,20],tgtm:38,subregclasslist:66,mlimit:41,progbit:35,"__nv_truncf":11,committe:[20,102],libtinfo:12,ui
 nt16_t:[78,76,115,66],unclear:[19,33],galina:126,wonder:[101,113,114,108,30,43,16],arriv:114,chmod:38,walk:[48,71,50,76,86,20],rpc:5,"_var":81,respect:[101,102,40,59,62,113,58,36,8,13,123,19,93,64,66,114,82,33,89,38,41,72,20,94,43,120,45],rpo:71,getoperand:[94,101,20,66],decent:[25,57,27,52,104,86,20],xxxcallingconv:66,compos:[80,107,83,96,36,62,9],compon:[],besid:[101,0,66,28,32,13,18,36,111,22],safepoint_token1:40,unregist:86,inbound:[80,36,63,114],presenc:[113,66,7,51,94,53,36,120,20],sock_stream:5,gtx:11,llparser:57,present:[],xorrr:66,align:[],dfpregsclass:66,create_entry_block_alloca:19,wili:114,wild:[18,28,32],xorri:66,indirectstubsmgrbuild:6,bb3:36,bb2:[36,124],bb1:[36,124],d_ctor_bas:7,layer:[],avx:[13,47,36,1],instrinfo:[],cctype:[24,25,111,29,30,31,32,33],eptr:36,avl:20,dual:43,add64mi32:8,tempor:36,incq:7,getattributespellinglistindex:34,uint16x4_t:88,headlight:101,xxxschedul:66,member:[],binary_preced:[18,19],largest:[36,94,35,63],ifndef:[5,6,59,62,9],f64:[94,36,66,11],
 expcnt:39,"0x1b":124,difficult:[25,101,58,36,28,53,32,43,99,120,18,127,20,42],slave:126,swiftself:36,ssecal:66,hardcodedsmalls:20,bcpl:46,decoupl:128,iftru:36,extra_dist:[],mcasmpars:94,immateri:50,firstli:36,foo_var:81,faultingload:100,linkagetyp:20,english:[38,101],initializeallasmprint:24,my_function_fast:11,llvm_enable_expensive_check:72,mips16:53,getoffset:66,camel:101,obtain:[],tcp:5,corei7:[13,1],heavili:[82,56,26,15,108],simultan:[1,42,53,13,88,20],tcb:95,expr1rh:80,rapid:43,methodproto:66,full_corpus_dir:42,eatomtypenul:115,parseandsquareroot:20,smith:101,cultur:102,waypoint:93,emitobject:85,registerehframesinprocess:5,llvm_on_win32:4,llvmdisassembler_option_usemarkup:45,agnost:[4,94,115,88],strconcat:[46,66,128],intregsregisterclass:66,lightweight:[101,2,20],destreg:94,denser:[18,32],press:24,librarynam:[82,86,64],python2:52,"7e15":28,hostc:11,hostb:11,hosta:11,incred:[43,101],bpf_class:94,repurpos:115,"0xff":[36,128],createphi:[24,25,31,32,33],growth:[36,94,20],"export":[
 38,72,58,36,28,94,32,104,75,99,5,6,59,62,9],superclass:[66,58,86,20,8,128],smoothli:[62,81],xxxsubtarget:66,containsfoo:101,not_found:[16,17,18,19,22,23],leaf:[120,115],image_sym_class_struct_tag:121,lead:[25,59,101,114,48,7,28,94,53,76,75,111,36,81,20,42,22,128],leak:[82,2,61],boolean_property_nam:44,leap:119,leaq:95,leav:[48,73,119,66,38,82,50,28,2,115,75,43,11,36,62,108],prehead:[17,31,48],leader:101,int32:97,investig:[51,26,15,9],settargettripl:24,acronym:56,dosometh:101,tdfile:[],xxxgencallingconv:66,obei:36,eatomtypenameflag:115,toolchain:[],linger:[],column:[80,25,101,38,36,51,1,115,76,78,7],fudg:12,vset_lan:88,constructor:[],spiller:[90,87,94],disabl:[],stackentri:82,projlibsopt:[],isnul:101,own:[],tight:[99,63],automat:[],warranti:[86,43],automak:[],isprint:42,"59620e187c6ac38b36382685ccd2b63b":51,build_mod:96,val:[24,25,101,66,11,36,28,29,30,31,32,33,53,97,124,68,5,20,111,128],transfer:[24,25,61,30,31,32,33,14,95,88,120,36],llvmattribut:47,secret:54,threadsanit:36,intentio
 n:[86,111,101,36,22],appl:[],arg1:[27,36,21],eltsizeparam:36,varexpr:[24,25,19,33],mailer:43,"0x7fffffff":36,callgraphscc:86,lazyresolverfn:66,made:[100,48,101,76,50,26,104,36,8,9,56,58,115,108,15,63,40,17,19,20,64,113,114,110,30,31,33,86,34,88,120,94,95,43,124,127],temp:[47,73],whether:[],distract:43,divisionbyzero:36,libsystem:101,ptrreg:94,lvm:25,fldcw:94,llvmasmpars:64,numberexpr:[24,25,111,29,30,31,32,33,16,17,18,19,22,23],significantli:[100,101,72,124,120,36,42,31,86,43,99,111,55,17,20,47,22],link_libs_in_shar:[],meaningless:20,rl5:11,constprop:[],"8bit":42,workabl:[],findsymbolin:62,rl7:11,mutual:[40,27,28,21,23],targetfunc:20,throwinfo:120,minsizerel:[38,72],the_modul:[16,17,18,19,23],percent:58,constantfold:57,book:[86,56,101,71,20],bool:[101,76,50,36,62,57,113,58,16,17,18,19,20,23,24,25,66,28,29,30,31,32,33,86,72,42,94,53],branch:[],modulehandlet:9,gline:1,neelakantam:48,inst_iter:20,auxiliari:[66,9],hacker:[56,43],junk:[16,17,18,19,22,23],package_vers:72,vea6bbv2:43,index
 edmap:[],add_subdirectori:72,tok_extern:[24,25,27,111,29,30,31,32,33],swifterror:36,debian:[74,38,47,12],stringmap:[],experienc:93,ani:[],sass:11,reliabl:[],space:[],pdata:35,emerg:109,keep_symbol:[],invari:[],istermin:[8,128]},objtypes:{"0":"std:option"},objnames:{"0":["std","option","option"]},filenames:["ReportingGuide","Vectorizers","CommandGuide/lit","BranchWeightMetadata","SystemLibrary","tutorial/BuildingAJIT5","tutorial/BuildingAJIT4","CommandGuide/FileCheck","TableGen/index","tutorial/BuildingAJIT1","CommandGuide/llvm-extract","NVPTXUsage","HowToCrossCompileLLVM","TestingGuide","CompileCudaWithLLVM","tutorial/OCamlLangImpl8","tutorial/OCamlLangImpl4","tutorial/OCamlLangImpl5","tutorial/OCamlLangImpl6","tutorial/OCamlLangImpl7","ProgrammersManual","tutorial/OCamlLangImpl1","tutorial/OCamlLangImpl2","tutorial/OCamlLangImpl3","tutorial/LangImpl08","tutorial/LangImpl09","tutorial/LangImpl10","tutorial/LangImpl01","CommandLine","tutorial/LangImpl03","tutorial/LangImpl04","tutori
 al/LangImpl05","tutorial/LangImpl06","tutorial/LangImpl07","TableGen/BackEnds","Extensions","LangRef","CommandGuide/llvm-nm","GettingStarted","AMDGPUUsage","Statepoints","CommandGuide/bugpoint","LibFuzzer","DeveloperPolicy","LLVMBuild","MarkedUpDisassembly","TableGen/LangRef","ReleaseNotes","Passes","ReleaseProcess","MergeFunctions","TestSuiteMakefileGuide","HowToBuildOnARM","Atomics","ScudoHardenedAllocator","CommandGuide/llvm-bcanalyzer","index","ExtendingLLVM","AliasAnalysis","tutorial/BuildingAJIT3","CommandGuide/llvm-diff","InAlloca","tutorial/BuildingAJIT2","Frontend/PerformanceTips","Projects","tutorial/index","WritingAnLLVMBackend","CommandGuide/llvm-build","HowToUseAttributes","CommandGuide/llvm-readobj","BlockFrequencyTerminology","Lexicon","CMake","HowToSubmitABug","Packaging","GoldPlugin","YamlIO","CommandGuide/index","HowToUseInstrMappings","CommandGuide/llvm-stress","CoverageMappingFormat","CMakePrimer","GarbageCollection","MIRLangRef","CommandGuide/opt","MCJITDesignAn
 dImplementation","WritingAnLLVMPass","CommandGuide/llc","BigEndianNEON","CommandGuide/llvm-symbolizer","CommandGuide/lli","TableGenFundamentals","CommandGuide/llvm-link","Bugpoint","CodeGenerator","SegmentedStacks","GettingStartedVS","StackMaps","CommandGuide/llvm-dwarfdump","LinkTimeOptimization","FaultMaps","CodingStandards","CodeOfConduct","CommandGuide/llvm-dis","HowToReleaseLLVM","CommandGuide/llvm-cov","CommandGuide/llvm-as","CommandGuide/llvm-ar","FAQ","DebuggingJITedCode","TableGen/Deficiencies","tutorial/LangImpl02","CommandGuide/llvm-config","HowToSetUpLLVMStyleRTTI","GetElementPtr","SourceLevelDebugging","CommandGuide/llvm-lib","CompilerWriterInfo","CommandGuide/tblgen","Phabricator","ExceptionHandling","yaml2obj","CommandGuide/llvm-profdata","TypeMetadata","BitCodeFormat","AdvancedBuilds","HowToAddABuilder","SphinxQuickstartTemplate","TableGen/LangIntro"],titles:["Reporting Guide","Auto-Vectorization in LLVM","lit - LLVM Integrated Tester","LLVM Branch Weight Metadata","
 System Library","5. Building a JIT: Remote-JITing – Process Isolation and Laziness at a Distance","4. Building a JIT: Extreme Laziness - Using Compile Callbacks to JIT from ASTs","FileCheck - Flexible pattern matching file verifier","TableGen","1. Building a JIT: Starting out with KaleidoscopeJIT","llvm-extract - extract a function from an LLVM module","User Guide for NVPTX Back-end","How To Cross-Compile Clang/LLVM using Clang/LLVM","LLVM Testing Infrastructure Guide","Compiling CUDA C/C++ with LLVM","8. Kaleidoscope: Conclusion and other useful LLVM tidbits","4. Kaleidoscope: Adding JIT and Optimizer Support","5. Kaleidoscope: Extending the Language: Control Flow","6. Kaleidoscope: Extending the Language: User-defined Operators","7. Kaleidoscope: Extending the Language: Mutable Variables","LLVM Programmer’s Manual","1. Kaleidoscope: Tutorial Introduction and the Lexer","2. Kaleidoscope: Implementing a Parser and AST","3. Kaleidoscope: Code generation to LLVM IR","8. Ka
 leidoscope: Compiling to Object Code","9. Kaleidoscope: Adding Debug Information","10. Kaleidoscope: Conclusion and other useful LLVM tidbits","1. Kaleidoscope: Tutorial Introduction and the Lexer","CommandLine 2.0 Library Manual","3. Kaleidoscope: Code generation to LLVM IR","4. Kaleidoscope: Adding JIT and Optimizer Support","5. Kaleidoscope: Extending the Language: Control Flow","6. Kaleidoscope: Extending the Language: User-defined Operators","7. Kaleidoscope: Extending the Language: Mutable Variables","TableGen BackEnds","LLVM Extensions","LLVM Language Reference Manual","llvm-nm - list LLVM bitcode and object file’s symbol table","Getting Started with the LLVM System","User Guide for AMDGPU Back-end","Garbage Collection Safepoints in LLVM","bugpoint - automatic test case reduction tool","libFuzzer \u2013 a library for coverage-guided fuzz testing.","LLVM Developer Policy","LLVMBuild Guide","LLVM’s Optional Rich Disassembly Output","TableGen Language Reference","LLV
 M 3.9 Release Notes","LLVM’s Analysis and Transform Passes","How To Validate a New Release","MergeFunctions pass, how it works","LLVM test-suite Guide","How To Build On ARM","LLVM Atomic Instructions and Concurrency Guide","Scudo Hardened Allocator","llvm-bcanalyzer - LLVM bitcode analyzer","Overview","Extending LLVM: Adding instructions, intrinsics, types, etc.","LLVM Alias Analysis Infrastructure","3. Building a JIT: Per-function Lazy Compilation","llvm-diff - LLVM structural ‘diff’","Design and Usage of the InAlloca Attribute","2. Building a JIT: Adding Optimizations – An introduction to ORC Layers","Performance Tips for Frontend Authors","Creating an LLVM Project","LLVM Tutorial: Table of Contents","Writing an LLVM Backend","llvm-build - LLVM Project Build Utility","How To Use Attributes","llvm-readobj - LLVM Object Reader","LLVM Block Frequency Terminology","The LLVM Lexicon","Building LLVM with CMake","How to submit an LLVM bug report","Advice on Packag
 ing LLVM","The LLVM gold plugin","YAML I/O","LLVM Command Guide","How To Use Instruction Mappings","llvm-stress - generate random .ll files","LLVM Code Coverage Mapping Format","CMake Primer","Garbage Collection with LLVM","Machine IR (MIR) Format Reference Manual","opt - LLVM optimizer","MCJIT Design and Implementation","Writing an LLVM Pass","llc - LLVM static compiler","Using ARM NEON instructions in big endian mode","llvm-symbolizer - convert addresses into source code locations","lli - directly execute programs from LLVM bitcode","TableGen Fundamentals","llvm-link - LLVM bitcode linker","LLVM bugpoint tool: design and usage","The LLVM Target-Independent Code Generator","Segmented Stacks in LLVM","Getting Started with the LLVM System using Microsoft Visual Studio","Stack maps and patch points in LLVM","llvm-dwarfdump - print contents of DWARF sections","LLVM Link Time Optimization: Design and Implementation","FaultMaps and implicit checks","LLVM Coding Standards","LLVM Community
  Code of Conduct","llvm-dis - LLVM disassembler","How To Release LLVM To The Public","llvm-cov - emit coverage information","llvm-as - LLVM assembler","llvm-ar - LLVM archiver","Frequently Asked Questions (FAQ)","Debugging JIT-ed Code With GDB","TableGen Deficiencies","2. Kaleidoscope: Implementing a Parser and AST","llvm-config - Print LLVM compilation options","How to set up LLVM-style RTTI for your class hierarchy","The Often Misunderstood GEP Instruction","Source Level Debugging with LLVM","llvm-lib - LLVM lib.exe compatible library tool","Architecture & Platform Information for Compiler Writers","tblgen - Target Description To C++ Code Generator","Code Reviews with Phabricator","Exception Handling in LLVM","yaml2obj","llvm-profdata - Profile data tool","Type Metadata","LLVM Bitcode File Format","Advanced Build Configurations","How To Add Your Build Configuration To LLVM Buildbot Infrastructure","Sphinx Quickstart Template","TableGen Language Introduction"],objects:{"":{"--s
 tats":[87,0,1,"cmdoption--stats"],"-D":[37,0,1,"cmdoption-llvm-nm-D"],"-A":[37,0,1,"cmdoption-llvm-nm-A"],"-name-regex":[105,0,1,"cmdoption-llvm-cov-show-name-regex"],"-B":[37,0,1,"cmdoption-llvm-nm-B"],"-":[84,0,1,"cmdoption-"],"-O":[87,0,1,"cmdoption-O"],"-seed":[79,0,1,"cmdoption-seed"],"-elf-section-groups":[69,0,1,"cmdoption-elf-section-groups"],"-mattr":[90,0,1,"cmdoption-mattr"],"-pretty-print":[89,0,1,"cmdoption-pretty-print"],"-print-address":[89,0,1,"cmdoption-print-address"],"-gen-register-info":[118,0,1,"cmdoption-tblgen-gen-register-info"],"-gen-subtarget":[118,0,1,"cmdoption-tblgen-gen-subtarget"],"-S":[37,0,1,"cmdoption-llvm-nm-S"],"-binary":[122,0,1,"cmdoption-llvm-profdata-merge-binary"],"-verify-each":[84,0,1,"cmdoption-verify-each"],"-counts":[122,0,1,"cmdoption-llvm-profdata-show-counts"],"-region-coverage-gt":[105,0,1,"cmdoption-llvm-cov-show-region-coverage-gt"],"-d":[92,0,1,"cmdoption-d"],"-g":[37,0,1,"cmdoption-llvm-nm-g"],"--object-directory":[105,0,1,"cmdop
 tion-llvm-cov-gcov--object-directory"],"-a":[2,0,1,"cmdoption-a"],"-c":[105,0,1,"cmdoption-llvm-cov-gcov-c"],"-b":[105,0,1,"cmdoption-llvm-cov-gcov-b"],"--no-progress-bar":[2,0,1,"cmdoption--no-progress-bar"],"-l":[105,0,1,"cmdoption-llvm-cov-gcov-l"],"-o":[37,0,1,"cmdoption-llvm-nm-o"],"-n":[37,0,1,"cmdoption-llvm-nm-n"],"--long-file-names":[105,0,1,"cmdoption-llvm-cov-gcov--long-file-names"],"--defined-only":[37,0,1,"cmdoption-llvm-nm--defined-only"],"-j":[2,0,1,"cmdoption-j"],"-u":[37,0,1,"cmdoption-llvm-nm-u"],"-t":[37,0,1,"cmdoption-llvm-nm-t"],"-v":[92,0,1,"cmdoption-v"],"-q":[2,0,1,"cmdoption-q"],"-p":[105,0,1,"cmdoption-llvm-cov-gcov-p"],"-s":[69,0,1,"cmdoption-s"],"-r":[69,0,1,"cmdoption-r"],"-gen-dag-isel":[118,0,1,"cmdoption-tblgen-gen-dag-isel"],"-show-line-counts-or-regions":[105,0,1,"cmdoption-llvm-cov-show-show-line-counts-or-regions"],"-show-instantiations":[105,0,1,"cmdoption-llvm-cov-show-show-instantiations"],"-force-interpreter":[90,0,1,"cmdoption-force-interpret
 er"],"--max-tests":[2,0,1,"cmdoption--max-tests"],"-class":[118,0,1,"cmdoption-tblgen-class"],"--max-time":[2,0,1,"cmdoption--max-time"],"-I":[118,0,1,"cmdoption-tblgen-I"],"-line-coverage-gt":[105,0,1,"cmdoption-llvm-cov-show-line-coverage-gt"],"-instr":[122,0,1,"cmdoption-llvm-profdata-show-instr"],"-input-files":[122,0,1,"cmdoption-llvm-profdata-merge-input-files"],"-sparse":[122,0,1,"cmdoption-llvm-profdata-merge-sparse"],"-regalloc":[90,0,1,"cmdoption-regalloc"],"-all-functions":[122,0,1,"cmdoption-llvm-profdata-show-all-functions"],"-use-color":[105,0,1,"cmdoption-llvm-cov-show-use-color"],"-pre-RA-sched":[90,0,1,"cmdoption-pre-RA-sched"],"-nodetails":[55,0,1,"cmdoption-llvm-bcanalyzer-nodetails"],"-Xdemangler":[105,0,1,"cmdoption-llvm-cov-show-Xdemangler"],"--vg-leak":[2,0,1,"cmdoption--vg-leak"],"-format":[105,0,1,"cmdoption-llvm-cov-show-format"],"-fake-argv0":[90,0,1,"cmdoption-fake-argv0"],"-demangle":[89,0,1,"cmdoption-demangle"],"--branch-probabilities":[105,0,1,"cmdopt
 ion-llvm-cov-gcov--branch-probabilities"],"--all-blocks":[105,0,1,"cmdoption-llvm-cov-gcov--all-blocks"],"-P":[37,0,1,"cmdoption-llvm-nm-P"],"--print-file-name":[37,0,1,"cmdoption-llvm-nm--print-file-name"],"-stats":[84,0,1,"cmdoption-stats"],"-name":[105,0,1,"cmdoption-llvm-cov-show-name"],"-gen-asm-writer":[118,0,1,"cmdoption-tblgen-gen-asm-writer"],"-symbols":[69,0,1,"cmdoption-symbols"],"-print-sets":[118,0,1,"cmdoption-tblgen-print-sets"],"-program-headers":[69,0,1,"cmdoption-program-headers"],"--check-prefixes":[7,0,1,"cmdoption--check-prefixes"],"-dyn-symbols":[69,0,1,"cmdoption-dyn-symbols"],"--show-xfail":[2,0,1,"cmdoption--show-xfail"],"-obj":[89,0,1,"cmdoption-obj"],"--check-prefix":[7,0,1,"cmdoption--check-prefix"],"--succinct":[2,0,1,"cmdoption--succinct"],"--x86-asm-syntax":[87,0,1,"cmdoption--x86-asm-syntax"],"--show-suites":[2,0,1,"cmdoption--show-suites"],"-spiller":[90,0,1,"cmdoption-spiller"],"-relocations":[69,0,1,"cmdoption-relocations"],"-gcc":[122,0,1,"cmdopti
 on-llvm-profdata-merge-gcc"],"-show-line-counts":[105,0,1,"cmdoption-llvm-cov-show-show-line-counts"],"-needed-libs":[69,0,1,"cmdoption-needed-libs"],"-line-coverage-lt":[105,0,1,"cmdoption-llvm-cov-show-line-coverage-lt"],"-output-dir":[105,0,1,"cmdoption-llvm-cov-show-output-dir"],"--enable-no-nans-fp-math":[87,0,1,"cmdoption--enable-no-nans-fp-math"],"-asmwriternum":[118,0,1,"cmdoption-tblgen-asmwriternum"],"-join-liveintervals":[90,0,1,"cmdoption-join-liveintervals"],"-debug-dump":[98,0,1,"cmdoption-debug-dump"],"--print-machineinstrs":[87,0,1,"cmdoption--print-machineinstrs"],"-asmparsernum":[118,0,1,"cmdoption-tblgen-asmparsernum"],"-section-symbols":[69,0,1,"cmdoption-section-symbols"],"--print-size":[37,0,1,"cmdoption-llvm-nm--print-size"],"-h":[69,0,1,"cmdoption-h"],"--config-prefix":[2,0,1,"cmdoption--config-prefix"],"--show-all":[2,0,1,"cmdoption--show-all"],"-f":[122,0,1,"cmdoption-llvm-profdata-merge-f"],"-function":[122,0,1,"cmdoption-llvm-profdata-show-function"],"-pr
 int-records":[118,0,1,"cmdoption-tblgen-print-records"],"-gen-dfa-packetizer":[118,0,1,"cmdoption-tblgen-gen-dfa-packetizer"],"--load":[87,0,1,"cmdoption--load"],"-dump":[55,0,1,"cmdoption-llvm-bcanalyzer-dump"],"-nozero-initialized-in-bss":[90,0,1,"cmdoption-nozero-initialized-in-bss"],"--quiet":[2,0,1,"cmdoption--quiet"],"--match-full-lines":[7,0,1,"cmdoption--match-full-lines"],"-disable-post-RA-scheduler":[90,0,1,"cmdoption-disable-post-RA-scheduler"],"-enable-unsafe-fp-math":[90,0,1,"cmdoption-enable-unsafe-fp-math"],"--spiller":[87,0,1,"cmdoption--spiller"],"-gen-instr-info":[118,0,1,"cmdoption-tblgen-gen-instr-info"],"-meabi":[87,0,1,"cmdoption-meabi"],"-gen-intrinsic":[118,0,1,"cmdoption-tblgen-gen-intrinsic"],"-sections":[69,0,1,"cmdoption-sections"],"--enable-unsafe-fp-math":[87,0,1,"cmdoption--enable-unsafe-fp-math"],"-arch":[105,0,1,"cmdoption-llvm-cov-report-arch"],"--unconditional-branches":[105,0,1,"cmdoption-llvm-cov-gcov--unconditional-branches"],"-strip-debug":[84,
 0,1,"cmdoption-strip-debug"],"--size-sort":[37,0,1,"cmdoption-llvm-nm--size-sort"],"-version":[105,0,1,"cmdoption-llvm-cov-gcov-version"],"-section-data":[69,0,1,"cmdoption-section-data"],"-size":[79,0,1,"cmdoption-size"],"--enable-no-infs-fp-math":[87,0,1,"cmdoption--enable-no-infs-fp-math"],"--path":[2,0,1,"cmdoption--path"],"-text":[122,0,1,"cmdoption-llvm-profdata-show-text"],"-time-passes":[84,0,1,"cmdoption-time-passes"],"-march":[90,0,1,"cmdoption-march"],"--show-unsupported":[2,0,1,"cmdoption--show-unsupported"],"-disable-inlining":[84,0,1,"cmdoption-disable-inlining"],"--time-passes":[87,0,1,"cmdoption--time-passes"],"-region-coverage-lt":[105,0,1,"cmdoption-llvm-cov-show-region-coverage-lt"],"--vg":[2,0,1,"cmdoption--vg"],"--show-tests":[2,0,1,"cmdoption--show-tests"],"--dynamic":[37,0,1,"cmdoption-llvm-nm--dynamic"],"--no-output":[105,0,1,"cmdoption-llvm-cov-gcov--no-output"],"-help":[55,0,1,"cmdoption-llvm-bcanalyzer-help"],"--radix":[37,0,1,"cmdoption-llvm-nm--radix"],"
 --undefined-only":[37,0,1,"cmdoption-llvm-nm--undefined-only"],"-jit-enable-eh":[90,0,1,"cmdoption-jit-enable-eh"],"-show-regions":[105,0,1,"cmdoption-llvm-cov-show-show-regions"],"--shuffle":[2,0,1,"cmdoption--shuffle"],"--extern-only":[37,0,1,"cmdoption-llvm-nm--extern-only"],"-enable-no-nans-fp-math":[90,0,1,"cmdoption-enable-no-nans-fp-math"],"--preserve-paths":[105,0,1,"cmdoption-llvm-cov-gcov--preserve-paths"],"--branch-counts":[105,0,1,"cmdoption-llvm-cov-gcov--branch-counts"],"-load":[84,0,1,"cmdoption-load"],"-expand-relocs":[69,0,1,"cmdoption-expand-relocs"],"--disable-excess-fp-precision":[87,0,1,"cmdoption--disable-excess-fp-precision"],"--format":[37,0,1,"cmdoption-llvm-nm--format"],"-print-enums":[118,0,1,"cmdoption-tblgen-print-enums"],"-use-symbol-table":[89,0,1,"cmdoption-use-symbol-table"],"-enable-no-infs-fp-math":[90,0,1,"cmdoption-enable-no-infs-fp-math"],"-filetype":[87,0,1,"cmdoption-filetype"],"-gen-emitter":[118,0,1,"cmdoption-tblgen-gen-emitter"],"-unwind":
 [69,0,1,"cmdoption-unwind"],"-gen-pseudo-lowering":[118,0,1,"cmdoption-tblgen-gen-pseudo-lowering"],"-verify":[55,0,1,"cmdoption-llvm-bcanalyzer-verify"],"-gen-tgt-intrinsic":[118,0,1,"cmdoption-tblgen-gen-tgt-intrinsic"],"--help":[105,0,1,"cmdoption-llvm-cov-gcov--help"],"--implicit-check-not":[7,0,1,"cmdoption--implicit-check-not"],"-x86-asm-syntax":[90,0,1,"cmdoption-x86-asm-syntax"],"-disable-opt":[84,0,1,"cmdoption-disable-opt"],"-mcpu":[90,0,1,"cmdoption-mcpu"],"-relocation-model":[90,0,1,"cmdoption-relocation-model"],"-file-headers":[69,0,1,"cmdoption-file-headers"],"--debug-syms":[37,0,1,"cmdoption-llvm-nm--debug-syms"],"--verbose":[2,0,1,"cmdoption--verbose"],"-debug":[84,0,1,"cmdoption-debug"],"-code-model":[90,0,1,"cmdoption-code-model"],"--function-summaries":[105,0,1,"cmdoption-llvm-cov-gcov--function-summaries"],"-sample":[122,0,1,"cmdoption-llvm-profdata-show-sample"],"--param":[2,0,1,"cmdoption--param"],"-dynamic-table":[69,0,1,"cmdoption-dynamic-table"],"-inlining":
 [89,0,1,"cmdoption-inlining"],"--vg-arg":[2,0,1,"cmdoption--vg-arg"],"-functions":[89,0,1,"cmdoption-functions"],"-section-relocations":[69,0,1,"cmdoption-section-relocations"],"--debug":[2,0,1,"cmdoption--debug"],"--disable-fp-elim":[87,0,1,"cmdoption--disable-fp-elim"],"-mtriple":[90,0,1,"cmdoption-mtriple"],"--numeric-sort":[37,0,1,"cmdoption-llvm-nm--numeric-sort"],"--threads":[2,0,1,"cmdoption--threads"],"--strict-whitespace":[7,0,1,"cmdoption--strict-whitespace"],"-gen-fast-isel":[118,0,1,"cmdoption-tblgen-gen-fast-isel"],"-gen-disassembler":[118,0,1,"cmdoption-tblgen-gen-disassembler"],"-gen-asm-matcher":[118,0,1,"cmdoption-tblgen-gen-asm-matcher"],"-show-expansions":[105,0,1,"cmdoption-llvm-cov-show-show-expansions"],"--time-tests":[2,0,1,"cmdoption--time-tests"],"-soft-float":[90,0,1,"cmdoption-soft-float"],"--no-sort":[37,0,1,"cmdoption-llvm-nm--no-sort"],"--object-file":[105,0,1,"cmdoption-llvm-cov-gcov--object-file"],"-dsym-hint":[89,0,1,"cmdoption-dsym-hint"],"--input-f
 ile":[7,0,1,"cmdoption--input-file"],"-st":[69,0,1,"cmdoption-st"],"-disable-spill-fusing":[90,0,1,"cmdoption-disable-spill-fusing"],"-sr":[69,0,1,"cmdoption-sr"],"-gen-enhanced-disassembly-info":[118,0,1,"cmdoption-tblgen-gen-enhanced-disassembly-info"],"--regalloc":[87,0,1,"cmdoption--regalloc"],"-output":[122,0,1,"cmdoption-llvm-profdata-show-output"],"-sd":[69,0,1,"cmdoption-sd"],"-default-arch":[89,0,1,"cmdoption-default-arch"],"-weighted-input":[122,0,1,"cmdoption-llvm-profdata-merge-weighted-input"],"-disable-excess-fp-precision":[90,0,1,"cmdoption-disable-excess-fp-precision"]}},titleterms:{callingconv:34,prefix:[36,7],undef:108,"const":50,lsda:120,globalvari:20,concret:113,everi:101,"void":[50,36],module_code_funct:124,clangattrclass:34,type_code_numentri:124,vector:[48,114,20,36,1],verif:40,x86_64:12,paramattr_block:124,bitstream:124,mcstreamer:94,direct:[39,1,7,94,13,35,97,36],getposit:28,ilist:20,aggreg:[48,36,63],llvmbuild:44,blockinfo:124,scalarenumerationtrait:76,hide
 :28,neg:114,poison:36,conduct:[0,102],"new":[86,48,57,58,49,120,115,33,13,19,20],postdomin:48,hasglobalalias:50,metadata:[100,123,3,36,11],elimin:48,amdgpu:[47,94,117,39],mem:36,copysign:36,lowerswitch:48,accur:36,studio:96,debugg:[48,36,115,93],valuemap:20,precis:[48,36],thinlto:47,portabl:[4,101,26,15,108],fsub:36,unit:[25,94],tst_code_entri:124,describ:63,would:50,init:36,dimacrofil:36,unpredict:36,call:[48,101,66,58,36,1,61,94,20,108],callgraph:[86,48],simplifycfg:[48,108],type:[80,48,57,101,66,1,20,76,123,63,36,81,114,46,128],tell:114,relat:66,warn:[57,101],unpack:38,must:[28,58],word:124,setup:[25,29,113,23],work:[40,38,114,115,50],targetframelow:94,root:82,overrid:58,phabric:119,give:[],coreclr:82,indic:[56,114,63,83],want:50,motion:48,end:[101,39,11,36,87,73,115,34,114,20,108],turn:[101,20,108],how:[94,126,113,114,49,50,42,73,12,52,104,75,14,34,68,78,20,108],tbaa:36,type_symtab_block:124,verifi:[48,108,7],config:112,updat:[104,58],attrdoc:34,after:[99,101,0],befor:101,wrong:
 [],arch:39,parallel:42,domin:48,opaqu:36,bootstrap:125,alias:[50,28,94,36,63],environ:86,reloc:[40,94,35],lambda:101,order:[76,36,63,88,53],frontend:63,over:[101,20,63],type_code_opaqu:124,fab:36,flexibl:7,clangstmtnod:34,fix:[50,94,20,115,124],strang:[],fadd:36,comprehens:47,erlang:82,safe:82,"break":[48,20],itanium:[120,117],spotless:[],each:48,debug:[25,58,115,77,109,13,48,20],foldingset:20,resum:36,extract:[48,10],content:[65,124,115,113,98],reader:69,got:73,dse:[48,58],umul:36,log2:36,barrier:[82,36,11],written:108,standard:[38,101,107,36,115,124,4,20],reconfigur:[],filter:[120,94],pointstoconstantmemori:58,fptoui:36,regress:13,cmpvalu:50,isa:20,size:[95,20],rang:[80,36],neededsafepoint:82,catchswitch:36,independ:[94,26,15,108],restrict:[120,63],lto_code_gen_t:99,instruct:[48,57,108,66,39,114,120,36,94,53,3,88,83,78,45,20],wrapper:[124,81],exp2:36,top:[28,46],type_code_struct:124,evolut:48,toi:42,namespac:101,tool:[38,41,108,77,122,116,96,93],lower:[82,48,36,114],bpf_ind:94,rem
 oveus:50,mergereturn:48,target:[24,48,94,66,11,47,26,104,35,90,15,114,118,36],keyword:101,provid:101,tree:[48,111,64,22],project:[38,72,67,47,75,81,44,64],aapc:88,consumeaft:28,modern:38,increment:43,strength:48,aliassettrack:58,preincrement:101,simplifi:[48,101],object:[24,38,65,36,114,115,85,37,124,69,20,64],lexic:46,breakpoint:86,phase:[94,99,66],tinyptrvector:20,don:[4,101,108,114],dom:48,doc:117,flow:[17,42,76,31,81],doe:[86,42,108,114],declar:[48,46,115],caml:65,dot:48,ldc:47,random:[50,54,79],syntax:[11,7,111,121,35,36,40,97,46,8,22,128],freeform:28,advisori:0,buildbot:[126,42],dfapacket:34,getanalysisusag:86,absolut:28,layout:[48,94,38,20,11,115,123,36,64],acquir:53,machineinstr:94,configur:[24,38,51,2,12,87,125,126],sroa:48,ditemplatetypeparamet:36,rich:45,predecessor:20,ceil:36,smul:36,report:[49,105,73,0],x86_mmx:36,"public":[14,101,20,104],basicblock:[50,20],commandlin:28,attributeset:68,bitvector:20,result:[40,2,58],miscompil:[73,93],respons:[48,28,58],fail:[],best:63,a
 war:113,hopefulli:127,discoveri:2,dicompileunit:36,diderivedtyp:36,mul:36,irc:56,approach:99,attribut:[48,83,28,61,115,43,68,36],extend:[57,94,31,32,33,17,18,19],extens:[28,31,115,86,35,17],lazi:[59,5,6,20,48],rtti:[101,113],notatom:53,cov:105,fault:100,diff:60,guid:[48,0,39,11,56,28,53,77,13,51,83,44,42],assum:36,duplic:[4,48],"__nvvm_reflect":11,basic:[48,72,113,66,27,111,83,124,77,21,86,9,36,50,122,20,8,22,63],quickli:38,deeper:113,type_code_x86_fp80:124,ani:[13,42],multithread:86,"catch":120,smallbitvector:20,read_regist:36,bitcod:[92,108,37,124,55,90,99],dissect:[80,11],properti:[26,15,63,115],slp:1,scalarrepl:[],anchor:101,mcsymbol:94,dwarfdump:98,globaldc:48,bitcast:36,perform:[63,1],make:[100,101,43,20,108],complex:[36,20,125],codeemitt:34,disubroutinetyp:36,fragil:13,reassoci:48,tune:87,libcal:[48,53],qualif:104,bewar:101,client:58,thi:[25,127,114,50,42,108,33,63,19,47],programm:20,identifi:[82,36],languag:[65,101,128,27,115,26,31,32,33,15,63,36,17,18,19,46,21,108],expos:4,
 patchpoint:97,elf:35,els:[17,101,31,81],opt:[86,28,84],subregist:83,background:[120,115,113,109],shadow:82,linux:117,specif:[94,72,107,26,115,104,13,87,15,63,35,4],deprec:51,manual:[36,28,117,20,83],unnecessari:101,underli:114,right:20,old:[],global_ctor:[108,36],interv:[48,94],argpromot:[48,58],type_code_fp128:124,intern:[48,28,101],indirect:36,global_dtor:36,functioncompar:50,subclass:[20,66],optparserdef:34,condit:48,core:20,aggress:48,memdep:48,codeview:115,tablegen:[91,94,34,110,46,8,128],promot:[48,66],post:48,chapter:[24,25,19,111,29,30,31,32,33,62,22,16,17,5,6,59,18,9,23],timelin:104,slightli:20,trophi:42,localescap:36,canonic:[48,36],commit:[43,119],looppass:86,instcombin:[48,108],"float":[36,35,90],encod:[80,94,124],bound:114,storag:[36,28,20],git:[38,119],wai:[20,114],support:[101,66,40,42,94,30,14,3,97,16,36,47,108],transform:[48,58],type_code_half:124,why:[25,114,50,42,108,33,19],avail:[82,58],width:[101,36,63,124],instrprof_incr:36,sitofp:36,analysi:[48,114,58,1,94,86,
 46],creation:85,form:[48,94],raw_ostream:101,modulepass:86,dead:48,heap:[82,20],icmp:36,profdata:122,inttoptr:[36,114],"__atomic_":53,fundament:[57,91],lowerinvok:48,emit:[24,82,105],featur:[74,101,1,82,42,94,13],yaml2obj:121,"abstract":[82,111,63,124,4,36,22],diagnost:1,exist:[86,19,58,33],nvvmreflect:11,check:[100,48,1,7,36,20],bswap:36,assembl:[106,39,66,82,94,35,88,36],floor:36,tip:[26,15,63],test:[38,123,72,49,83,42,2,104,13,43,41,36,51],node:[48,57,36],stackrestor:36,intend:61,smallset:20,put:24,addpreserv:86,consid:63,setjmp:120,pseudo:80,time:[25,99,73,101,75],offsetof:[26,15],backward:43,corpu:42,concept:[80,86,8],nearbyint:36,chain:[38,96,20,58],ptrtoint:[36,114],global:[48,1,50,115,83,36],lli:90,llc:87,primer:81,middl:108,depend:[74,48,35,58],graph:[48,20],readabl:101,uadd:36,sourc:[80,25,101,72,38,47,108,115,89,36,64],string:[80,36,20],administr:104,level:[80,48,101,36,28,94,115,88,83,4,46,108],did:108,die:48,iter:[20,1],item:38,quick:[80,86,72,82,28,13],round:36,paramat
 tr_code_entri:124,sign:[124,119],scev:[48,58],funclet:[120,36],appeal:0,defici:[8,110],deriv:[40,57,20],gener:[48,94,51,2,79,20,85,107,36,108,17,93,23,82,83,29,31,35,90,120,73,118,128],globalsmodref:[48,58],modif:3,address:[85,39,11,94,123,89,114,36],along:50,nondebug:48,extrem:6,safepoint:40,basiccg:48,localrecov:36,semant:[11,40,97,63,4,36],maxnum:36,extra:[13,114],modul:[24,48,10,101,36,86,81,20,62,83],prefer:[101,63],ipo:47,visibl:36,marker:36,instal:12,type_code_void:124,dagisel:34,emitt:66,memori:[48,58,36,33,63,19,20],univers:108,subvers:[38,119],live:[83,94],criteria:104,scope:[128,36,115,81],checkout:38,share:74,enhanc:40,visual:[96,72],prototyp:48,logarithm:50,ibm:117,registerinfo:34,prepar:85,uniqu:76,can:[108,63,114],topic:[65,20,72],critic:48,fp16:36,alwai:[48,114],multipl:20,targetsubtarget:94,write:[86,101,66,58,82,28,94,13,34,114,51,64,108],legalizetyp:94,foreach:46,map:[80,100,76,66,82,40,94,97,36,78,20],remap:85,armneonsema:34,targetmachin:94,smallstr:20,module_cod
 e_gcnam:124,mai:[50,58],data:[80,48,76,11,36,42,94,122,124,4,20],goal:82,stress:79,autotool:75,practic:63,assici:50,ebpf:94,predic:101,inform:[25,101,117,48,47,115,123,13,105,43,20],"switch":[36,3,101],combin:[48,94],runonbasicblock:86,mapvector:20,callabl:20,comdat:36,microscop:101,still:63,pointer:[58,1,40,114,36,20],dynam:[86,28,94,36],entiti:128,armneontest:34,group:[86,28,36],thumb:113,fastisel:34,polici:43,precondit:[],gen:11,platform:[13,117,108,72],jit:[65,66,59,94,30,109,16,5,6,20,62,9],cmptype:50,fuzzer:42,main:50,non:[82,48,47,125],synopsi:[103,2,105,55,7,10,106,107,79,60,112,67,84,116,87,89,90,69,92,122,37,41,98,118],initi:[101,58,82,42,94,20],half:36,now:[],introduct:[48,73,76,49,50,101,52,104,54,3,111,125,78,5,6,59,8,9,80,57,94,11,36,115,12,61,62,14,110,81,16,17,18,19,20,21,22,23,24,25,66,114,82,27,28,29,30,31,32,33,86,126,34,35,88,68,70,72,39,85,120,42,58,95,53,75,43,83,44,45,127,46,47,128],name:[48,101,66,28,94,115,36],getanalysi:86,revers:1,sequentiallyconsist:53,sj
 lj:120,callsit:[48,120],compil:[24,25,112,101,72,38,30,47,73,12,74,14,87,36,16,117,6,59,108],replac:[48,20],individu:[83,20],continu:101,releasememori:86,redistribut:108,operand:[40,97,36,66,83],happen:[108,0,114],switchinst:[48,3],catchret:36,armneon:34,space:[94,114,101,39,11],profil:[48,122],rational:[36,114],orc:62,clangattrvisitor:34,frequenc:70,ocaml:82,codegen:53,thing:[108,63],gcmetadataprint:82,frequent:[108,72],first:[36,114],oper:[107,36,32,33,63,18,19,20],directli:[90,58],type_code_arrai:124,rint:36,arrai:[80,35,20,36,114],stringref:20,submit:[43,73],crit:48,open:[47,108],module_code_datalayout:124,convent:[108,39,66,11,94,61,36],type_block:124,fma:36,clangsacheck:34,copi:[101,61],specifi:[82,86,28,63,58],pragma:1,than:114,xcore:117,posit:28,seri:70,pre:[49,2],loweratom:48,licm:[48,58],argument:[48,36,28,81,20,128],doiniti:86,recover:20,bitwis:36,engin:85,readcyclecount:36,advic:[74,93],note:[47,94,117,52],printer:[48,66],normal:76,c99:35,insertel:36,"_global__i_a":108,c
 mpoper:50,runtim:[120,36,1],mcjit:[85,109],lexicon:71,show:[105,108,122],atom:[48,36,53],concurr:[36,53],hack:[48,12],runonscc:86,slot:48,onli:[48,20],mergefunct:50,fenc:36,activ:40,behind:115,analyz:55,customwritebarri:82,offici:117,gep:[63,114],variou:48,get:[38,42,36,96,70],clang:[38,42,12,52,104,14,34,125],ssa:[48,94,108],targetjitinfo:94,requir:[38,114,58,82,28,94,13,96,86,64],intrins:[48,57,11,82,40,115,34,97,88,120,36],type_code_ppc_fp128:124,cmpconstant:50,where:108,summari:[38,114,88,55],kernel:11,gcwrite:[82,36],postdom:48,deadargelim:48,detect:[48,14],review:[43,119],enumer:101,label:[36,101,7],clangcommenthtmltagsproperti:34,enough:93,clangattrpchread:34,volatil:36,between:[86,99,20,114],"import":20,spars:48,parent:120,sparc:117,bitset:[],dimacro:36,region:[80,48,86],contract:113,audienc:66,tutori:[65,11,27,26,14,15,7,21],doesnotaccessmemori:58,frameaddress:36,acceler:115,pow:36,exploit:28,sccp:48,sentinel:20,rebuild:[],mark:11,basicaa:[48,58],fptrunc:36,"case":[41,43],m
 odule_code_vers:124,module_code_alia:124,type_code_point:124,cast:[20,114],invok:[48,20,36,11],tblgen:118,onlyreadsmemori:58,freelist:54,mergefunc:48,develop:[38,72,56,42,77,43],author:63,same:[20,7],rgpassmanag:86,binari:[111,108,32,104,18,36,22],document:[56,101,117,50,76,104,63],immutableset:20,exhaust:48,srem:36,ssub:36,preassign:94,nest:61,driver:[111,29,22,23],sreg:11,driven:58,value_symtab_block:124,setversionprint:28,extern:[48,28,47,51,65],defm:46,runonmachinefunct:86,macro:[76,20,81],markup:45,clobber:[94,36],without:108,model:[47,36,63],dereferenc:[114,81],customreadbarri:82,execut:[72,2,20,90,11],when:[42,101,93,63,108],s_waitcnt:39,neon:88,rest:[111,22],gdb:[86,109],smallvector:20,asmmatch:34,miscellan:[86,83,28,117,64],hint:[20,1],filecheck:7,except:[48,101,36,61,120],littl:101,versa:20,overview:[101,49,40,51,96,78,36,80,56,11,13,81,64,82,83,38,120,58,74,97,124,44],disubprogram:36,endcatch:120,earli:101,read:[82,50,99,66,11],amd:[],va_start:36,world:86,mod:48,intel:87,
 integ:[36,124,114],dilexicalblockfil:36,output:[76,51,28,2,55,45,36,42],targetinstrinfo:[94,66],deduct:101,trampolin:36,catchpad:36,freez:[],gvn:[48,58],definit:[97,71,101,128,55],achiev:20,legal:[94,63,66],exit:[48,101,103,2,105,55,79,10,106,107,7,60,112,67,84,87,89,90,69,92,122,37,41,98,118],refer:[48,82,20,28,36,83,44,46],garbag:[82,36,26,15,40],inspect:20,fpmath:36,clangattrimpl:34,"throw":[4,120],comparison:50,patent:43,stacklet:95,cuda:14,faultmap:100,routin:20,clangdiagsdef:34,effici:[61,58],bpf_ab:94,terminolog:[38,70],strip:48,your:[86,126,72,113],va_arg:36,log:[50,36],area:[40,36],hex:76,nvvm:11,start:[80,38,72,82,28,94,86,13,96,36,42,9],interfac:[4,108,20,119,58],low:101,clear_cach:36,kaleidoscop:[24,25,29,65,27,111,26,30,31,32,33,15,16,17,18,19,21,22,23],resolut:99,addrequiredtransit:86,hard:[25,19,33],jite:5,bundl:[94,36],getmodrefinfo:58,epilog:94,conclus:[111,26,15,22],notat:[38,46],tripl:[94,36,11],runonregion:86,"default":[101,76],embed:[83,72],loadabl:[],creat:[86,
 20,64,104],deep:127,deletevalu:58,file:[80,38,101,0,107,48,79,28,2,115,13,99,124,37,94,7,128],incorrect:73,collector:[82,36],multiclass:[46,128],field:50,valid:[49,76],copyright:43,you:[127,0],architectur:[40,117,97],formed:36,registri:86,sequenc:76,symbol:[89,48,37,99],ilist_trait:20,amd_kernel_code_t:39,ilist_nod:20,reduc:48,ipsccp:48,hsa_code_object_vers:39,directori:38,type_code_float:124,smrd:39,mask:36,hello:86,calle:61,mass:70,scudo:54,"__sync_":53,represent:[80,108,58],all:[24,48,108],dist:[],consider:[20,61,88],forbidden:101,scc:48,scalar:[48,76],ptx:11,follow:[50,114],ptr:[36,11],clangattrspellinglistindex:34,module_code_globalvar:124,tail:[48,94],program:[56,94,8,64,90],datalayout:94,type_code_funct:124,consum:115,faq:[42,108],urem:36,util:[40,38,76,67,48],candid:104,mechan:101,inteqclass:20,ia64:117,type_code_integ:124,induct:[48,1],list:[101,5,6,59,62,9,56,117,36,81,16,17,18,19,20,111,22,23,24,25,28,29,30,31,32,33,37,47,76],managedstat:20,adjust:[19,36,33],stderr:48,zer
 o:120,design:[85,56,114,93,94,61,54,99,20],pass:[100,48,72,58,50,30,86,63,40,16,20,83],further:64,enter_subblock:124,heartble:42,trick:[26,15],what:[0,114,82,50,42,108,86,63,93],xor:36,sub:[80,36],abi:[117,47,94,20,120],section:[100,97,127,35,98],ast:[17,111,6,31,22],abl:50,delet:[48,20],abbrevi:124,version:[42,101,109,104],subtarget:[34,66],ctpop:36,method:[86,4,101,20,58],full:[24,25,19,36,111,29,30,31,32,33,62,22,16,17,5,6,59,18,9,23],hash:115,berkelei:94,behaviour:35,analysisusag:86,prologu:36,lto_module_t:99,modifi:[28,108,36,107],valu:[48,108,114,50,28,76,115,36,83,128,46,20],trunc:36,search:50,ahead:25,shufflevector:36,pick:20,via:[51,119],primit:[124,128],transit:[40,36,120],filenam:36,select:[93,28,2,36,94],replacedirectcal:50,hexadecim:35,liber:101,regist:[48,108,66,11,83,94,86,63],two:[94,114],coverag:[80,105,42],unwindless:48,va_end:36,asm:[120,94,36],metadata_block:124,minor:39,more:[101,20,125],flat:39,tester:2,type_code_metadata:124,statepoint:[82,40,36],flag:[1,83,28
 ,74,14,36],known:110,cach:72,minnum:36,abandon:119,def:[46,20],indirectbr:36,registr:[86,66],emiss:[25,94,35],addrspacecast:36,templat:[36,127,20,128],dicompositetyp:36,readobj:69,newlin:7,programmat:20,anoth:20,immutablemap:20,phi:36,reject:108,unswitch:48,simpl:[48,20,36,11],isn:93,replacewithnewvalu:58,resourc:117,mccontext:94,reflect:11,exceptionpoint:120,arcanist:119,callback:6,help:[14,108,20,28,64],through:101,constants_block:124,hierarchi:[20,113],paramet:[36,11],style:[101,113,58,35,36,64],late:94,clangcommenthtmltag:34,gcov:105,systemz:117,good:42,"return":101,frem:36,complain:11,module_code_sectionnam:124,diglobalvari:36,globalvalu:20,token:[120,36],scalarevolut:48,fulli:101,subsystem:56,nightli:49,interleav:36,clangattrparsedattrimpl:34,weight:[3,70,122],branchinst:3,monoton:53,idea:[18,32],realli:108,linkag:36,expect:[3,36],longjmp:120,reduct:[48,41,1],safeti:[26,15],print:[86,48,112,98,58],subsubsect:127,occurr:28,qualifi:[108,104],advanc:[80,65,42,20,125],base:[48,108
 ,113,114,40,47,94],instrmap:78,begincatch:120,thread:[48,20,36],bitconvert:88,clangattrparsedattrkind:34,postdomtre:48,clangcommenthtmlnamedcharacterrefer:34,lifetim:[36,61,115],assign:[48,19,33],major:[43,39],number:[48,28,124],smallptrset:20,module_block:124,differ:[51,114,58],script:[49,81],interact:[86,20],construct:[48,94,108],statement:3,natur:48,store:[48,94,36,63,108],option:[103,2,105,54,55,7,10,106,107,79,13,20,112,67,28,84,87,89,90,69,38,72,92,42,122,37,41,98,45,118],relationship:20,selector:66,pars:[28,94,111,22],std:[101,20],remot:5,i32:114,remov:48,cost:120,valuesymbolt:20,tailcallelim:48,comput:[82,114,11],packag:74,"null":[82,114],built:[82,94,76,3,81],lib:[116,38],trip:1,self:108,lit:2,also:[10,101,106,107,103,2,87,55,90,37,41],exampl:[89,38,112,122,82,36,42,2,109,86,75,96,99,88,78,127,20,8],build:[65,72,126,67,42,108,12,52,104,86,75,14,64,125,44,5,6,59,62,9],extractvalu:36,extractel:36,brace:101,coff:[121,35],cleanuppad:36,distribut:[36,104],previou:[],machinebasic
 block:94,most:48,plan:86,mach:115,cover:101,sibl:94,exp:36,rewritestatepointsforgc:40,microsoft:[96,72],ctag:34,runonmodul:[86,50],gold:75,clangattrparsedattrlist:34,stackprotectorcheck:[],fine:20,find:[48,20,63],write_regist:36,writer:117,solut:[50,42],unus:[4,48],express:[80,48,36,111,29,31,120,17,128,7,22,23],nativ:[94,124],externalfnconst:48,diloc:36,statist:[86,20],immutablepass:86,set:[48,113,66,58,28,86,20],clangattrpchwrit:34,startup:42,mutabl:[19,33],see:[10,101,106,107,103,2,87,55,90,37,41],close:[48,29,23],arm:[117,47,12,52,35,88],seh:120,module_code_tripl:124,vop1:39,vop3:39,vop2:39,end_block:124,numer:14,unrol:[48,36,1],struct:[101,36,114],both:38,vopc:39,interprocedur:48,inalloca:61,debug_typ:20,context:76,let:[46,128],machinefunct:[86,94],load:[85,86,94,36,63],point:[82,36,35,97,90],schedul:[94,66],header:[80,4,54,101,115],alloca:[95,36,63],classof:113,functionpass:86,backend:[66,114,94,34,8,128],aarch64:117,diimportedent:36,strategi:[82,36],irtransformlay:62,understa
 nd:108,atomicrmw:36,dequ:20,look:63,fptosi:36,passmanag:86,"while":20,unifi:48,kick:[18,32],behavior:58,error:[4,101,20,76],anonym:[48,101],loop:[48,101,1,31,86,81,17,36,70,128],prolog:94,subsect:127,propag:48,reg2mem:48,runonfunct:86,demot:48,bitrevers:36,illinoi:108,targetlow:94,minim:4,clangdiagsindexnam:34,decod:48,higher:108,x86:[117,47,94,35],diobjcproperti:36,optim:[48,73,84,26,30,53,115,75,14,15,16,94,99,62,108],va_copi:36,user:[48,39,11,56,42,76,32,33,87,18,19,20],function_block:124,specialis:36,stack:[48,94,82,40,26,95,97,35,15,36],stateless:48,travers:20,task:[20,104],entri:[48,3,97],parenthes:101,person:36,propos:115,always_inlin:48,functionattr:48,module_code_asm:124,ipconstprop:48,ldr:88,mubuf:39,waymark:20,input:[76,36,122],type_code_label:124,vendor:39,format:[80,101,107,40,28,2,115,120,97,124,83,44,94,42],big:88,bia:70,ld1:88,bit:[36,28,20,124],pcre2:42,pcmarker:36,collect:[117,82,40,28,26,15,36],constmerg:48,clangdeclnod:34,often:114,cttz:36,back:[34,108,39,11],sam
 pl:[80,78],mirror:38,densemap:20,sizeof:[26,15],instcount:48,cmpgep:50,scale:70,glibc:[],per:59,substitut:[13,2],larg:63,bcanalyz:55,machin:[24,66,83,94,35,63],run:[51,11,42,2,12,86,8],step:[126,66,39],prerequisit:66,copyvalu:58,deadtypeelim:48,bugpoint:[48,93,41],constraint:36,indirectbrinst:3,dofin:86,runonloop:86,block:[48,101,36,76,124,83,20,70],gcroot:36,gcread:[82,36],chang:[119,47,29,115,43,20,23],announc:104,inclus:128,kaleidoscopejit:9,question:[108,102],fast:36,custom:[66,114,82,28,76,51],arithmet:[94,36,114],includ:[4,101,108,38],suit:[38,72,49,51,2,13],fmuladd:36,aliasanalysi:58,properli:101,lint:48,link:[38,92,11,75,96,99],cmpxchg:36,line:[28,119,1],info:[48,20,115,66,128],clangattrspel:34,consist:[4,101],fcmp:36,fdiv:36,impl:48,constant:[48,36,30,115,35,16,20],debugtrap:36,parser:[28,94,31,17,111,22],doesn:42,repres:[94,123],clangattrlist:34,cmake:[72,51,12,81],sequenti:20,cleanupret:36,llvm:[1,26,3,4,10,11,12,13,14,15,16,17,19,20,23,2,29,30,31,33,34,35,38,42,43,45,47,
 48,40,51,52,96,55,56,57,58,36,60,64,65,66,67,69,70,71,72,73,74,75,77,79,80,81,82,84,86,87,88,89,90,93,94,95,53,97,98,99,101,102,103,104,105,106,107,108,112,113,114,115,116,92,120,122,37,124,126],clean:[],callgraphsccpass:86,mismatch:108,domfronti:48,eval:[48,58],parseenvironmentopt:28,extrahelp:28,difil:36,svn:[38,119],typeid:120,lane:88,algorithm:[94,20],vice:20,intervalmap:20,llvm_shutdown:20,llvmcontext:20,code:[48,101,0,102,94,4,5,6,59,62,9,80,36,115,108,109,14,16,17,18,19,20,22,23,24,25,66,82,83,111,29,30,31,32,33,86,89,90,38,119,85,93,42,73,43,64,120,118,128],partial:[48,1],edg:48,addescapingus:58,queri:48,privat:101,friendli:42,send:38,dienumer:36,mcinst:94,probe:35,vla:114,stackguard:36,relev:117,magic:124,"try":120,udiv:36,cfg:[48,3],memset:36,jump:[48,94],fold:[16,94,30,66],instnam:48,compat:[116,42,43],index:114,twine:20,memcpyopt:[48,58],compar:[50,114],asmwrit:34,access:[50,43,36,94],experiment:[40,36,97],deduc:48,targetregisterinfo:[94,66],bodi:[48,46],objects:36,sext:
 [36,63],sink:48,implicit:100,convert:[89,36],convers:[11,36,66,1],vbr:124,implement:[85,65,94,88,66,58,82,50,111,26,95,86,99,15,36,4,20,70,22],hexagon:[],domtre:48,dyn_cast:20,api:[108,94,43,45,20,9],dinamespac:36,from:[38,10,114,48,28,94,12,90,6,36,70],commun:[56,99,102,104],upgrad:[],next:7,websit:104,sort:20,insertvalu:36,hierchari:20,landingpad:36,nvptx:[94,117,11],dwarf:[25,115,98],alia:[48,114,58,1,28,94,36],annot:[45,36],endian:88,scatter:[36,1],control:[17,14,81,28,31],quickstart:[13,75,127],process:[56,49,50,94,104,5],optioncategori:28,high:[80,101,83,94,4,36],tag:[80,47,76,115,104,20],tab:101,afl:42,gcc:47,getregisteredopt:28,usub:36,subdirectori:64,instead:101,sin:36,delai:54,fpext:36,overridden:50,constructor:101,targetdata:48,redund:48,philosophi:[99,93,115],physic:94,alloc:[95,54,94,20],sdiv:36,bind:[],counter:80,element:114,issu:[58,101,11],pseudolow:34,allow:28,deoptim:36,move:91,stacksav:36,getanalysisifavail:86,elis:61,narr:50,define_abbrev:124,initroot:82,infrastr
 uctur:[13,126,2,58],dag:[94,7,70],crash:[73,93],handl:[48,94,36,76,120,81,20],auto:[101,1],front:[115,73,108,114],successor:[83,20],module_code_purgev:124,mem2reg:48,fuzz:42,mode:[25,42,94,88],mnemon:94,basicblockpass:86,acquirereleas:53,denseset:20,postdomfronti:48,selectiondag:[57,94,66],chunk:54,licm_vers:36,clangcommentcommandlist:34,"static":[48,87,101],function_ref:20,patch:[38,43,97,104],dilexicalblock:36,special:[36,11],out:[72,9,114],variabl:[25,101,72,1,36,94,95,115,33,35,124,81,48,19,7,64],matrix:94,frontier:48,ret:36,categori:28,rel:36,hardwar:[38,96,117],barrier0:11,ref:48,math:36,common:[38,96,20,11],iostream:[101,108],lcssa:48,attrbuild:68,manipul:36,powerpc:[47,94,117],dictionari:42,deadarghax0r:48,releas:[49,47,53,104],indent:101,could:50,lexer:[17,21,31,27],ask:108,membership:123,keep:[4,101],length:35,outsid:53,lto:75,softwar:[38,96],pgo:125,qualiti:43,fmul:36,lshr:36,owner:43,unknown:1,licens:[75,43,108],system:[4,96,128,36,38],messag:43,regionpass:86,termin:36,"
 final":[85,104],misunderstood:114,tidbit:[26,15],deconstruct:94,debuginfo:48,uitofp:36,arrayref:20,exactli:42,steen:58,prune:48,structur:[1,50,51,60,13,36,83,20],charact:[7,124],bitvalu:76,clangattrparserstringswitch:34,mergetwofunct:50,linker:[99,36,92],have:114,tabl:[56,65,120,94,115,123,37],need:[127,114],printvar:[],disassembl:[94,45,34,103],mix:1,builtin:28,which:[114,58],mip:[47,117],mir:83,singl:[48,36],preliminari:66,segment:[94,95],"class":[101,113,66,58,20,28,94,86,36,78,46,128],memorydependenceanalysi:58,placement:[48,64],returnaddress:36,gather:[36,1],request:119,stackmap:97,determin:[28,125],linkonc:35,text:28,dbg:[48,115],findregress:49,module_code_deplib:124,trivial:[16,30],locat:[89,25,38],tire:[18,32],getelementptr:[108,36],should:[50,108],ditemplatevalueparamet:36,won:127,stackprotector:36,elseif:81,local:[19,38,2,36,33],memcpi:[48,36],enabl:36,organ:[13,4,44],possibl:[50,28,101],stuff:108,integr:[44,48,2],partit:48,contain:[42,20],shl:36,view:[48,20,81],altern:[28
 ,99],frame:[94,26,15,120],packet:94,polymorph:20,statu:[103,2,105,55,7,10,106,107,79,60,40,112,67,84,87,89,90,69,92,119,122,37,41,98,118],pattern:7,dll:36,state:50,instrprof_value_profil:36,kei:76,clangattrdump:34,isol:[5,20],diexpress:36,noalia:36,endl:101,addit:[47,2],doxygen:101,plugin:[82,75],leb128:80,etc:[57,20],instanc:128,grain:20,committe:0,comment:[101,128],parallel_loop_access:36,guidelin:127,hyphen:28,yaml:76,window:[117,42,35,120],compon:[44,42,94,112],packedvector:20,treat:[101,20],immedi:83,hsa_code_object_isa:39,ifunc:36,assert:101,togeth:24,mail:56,ptxa:11,present:50,multi:[99,125],align:[124,63,88],libfuzz:42,contextu:45,harden:54,defin:[101,66,2,32,33,18,19],sop2:39,layer:[94,62],sop1:39,demo:[108,104],instrinfo:34,site:20,avr:[],uglygep:114,archiv:[38,107],motiv:[100,97],mutat:[42,19,33],disubrang:36,cross:[38,12,72],sqrt:36,member:[20,0,114],donoth:36,clangdiaggroup:34,sopp:39,sadd:36,effect:[63,114],sopc:39,expand:66,mcsection:94,sparsebitvector:20,builder:126,
 well:36,thought:[29,23],powi:36,command:[119,1,28,77,122,105,81],choos:24,undefin:[36,11],setvector:20,libdevic:11,unari:[18,32],distanc:[5,114],"boolean":28,obtain:[14,43],memmov:36,virtual:[123,4,101,94,108],web:119,adt:20,makefil:[13,51,64],add:[126,36,114],cleanup:[120,61],adc:[48,58],match:[94,7],globalopt:48,indvar:48,clangcommentnod:34,placesafepoint:40,know:50,insert:[40,94,20],like:[101,20,108],type_code_vector:124,registeranalysisgroup:86,unord:53,soft:4,page:[108,104],unreach:[108,36],unabbrev_record:124,suppli:42,guarante:[26,15],stringset:20,librari:[38,101,36,28,74,54,116,4,20,42,64],nvcc:14,leak:42,avoid:[101,63],trap:36,codegenprepar:48,dce:48,usag:[72,1,61,122,75,54,97,93],host:[38,108],prefetch:36,offset:[123,36],clangattrtemplateinstanti:34,stage:125,about:[42,108],toolchain:38,uniquevector:20,type_code_doubl:124,lppassmanag:86,implicitnullcheck:100,zext:[36,63],disabl:36,ashr:36,metadata_attach:124,own:20,dibasictyp:36,automat:[93,36,41],guard:36,merg:[48,104,122
 ,50],machineinstrbuild:94,rotat:48,appl:125,"var":36,dilocalvari:36,log10:36,"function":[48,101,1,50,3,4,59,80,10,11,36,108,81,20,23,25,83,28,29,57,115,86,94],machinefunctionpass:86,gain:50,uninstal:[],overflow:[36,114],inlin:[48,101,36,94],bug:[73,113,49,40,60,37],liblto:99,count:[48,3,36,58,1],whether:28,record:[80,124],limit:[83,123,58],problem:[25,38,40,42,33,86,96,88,110,19],evalu:[48,101,58],descript:[103,2,105,55,7,10,106,107,79,60,93,112,67,84,116,87,89,90,69,92,94,122,37,41,98,118,99],dure:1,constprop:48,sparseset:20,probabl:70,detail:[101,1,95,115,104,55,45],parsecommandlineopt:28,other:[101,117,114,11,36,28,26,58,13,3,15,63,81,20,108],lookup:115,futur:[86,94],branch:[48,3,70,66,104],iplist:20,stat:20,indexedmap:20,clangcommentcommandinfo:34,addrequir:86,ctlz:36,sparsemultiset:20,stringmap:20,stai:43,sphinx:127,reliabl:94,customroot:82,rule:[114,36,113,104],vliw:94,invari:[48,36]}})
\ No newline at end of file

Added: www-releases/trunk/3.9.1/docs/tutorial/BuildingAJIT1.html
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/tutorial/BuildingAJIT1.html?rev=290368&view=auto
==============================================================================
--- www-releases/trunk/3.9.1/docs/tutorial/BuildingAJIT1.html (added)
+++ www-releases/trunk/3.9.1/docs/tutorial/BuildingAJIT1.html Thu Dec 22 14:04:03 2016
@@ -0,0 +1,583 @@
+
+<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN"
+  "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd">
+
+
+<html xmlns="http://www.w3.org/1999/xhtml">
+  <head>
+    <meta http-equiv="Content-Type" content="text/html; charset=utf-8" />
+    
+    <title>1. Building a JIT: Starting out with KaleidoscopeJIT — LLVM 3.9 documentation</title>
+    
+    <link rel="stylesheet" href="../_static/llvm-theme.css" type="text/css" />
+    <link rel="stylesheet" href="../_static/pygments.css" type="text/css" />
+    
+    <script type="text/javascript">
+      var DOCUMENTATION_OPTIONS = {
+        URL_ROOT:    '../',
+        VERSION:     '3.9',
+        COLLAPSE_INDEX: false,
+        FILE_SUFFIX: '.html',
+        HAS_SOURCE:  true
+      };
+    </script>
+    <script type="text/javascript" src="../_static/jquery.js"></script>
+    <script type="text/javascript" src="../_static/underscore.js"></script>
+    <script type="text/javascript" src="../_static/doctools.js"></script>
+    <link rel="top" title="LLVM 3.9 documentation" href="../index.html" />
+    <link rel="up" title="LLVM Tutorial: Table of Contents" href="index.html" />
+    <link rel="next" title="2. Building a JIT: Adding Optimizations – An introduction to ORC Layers" href="BuildingAJIT2.html" />
+    <link rel="prev" title="8. Kaleidoscope: Conclusion and other useful LLVM tidbits" href="OCamlLangImpl8.html" />
+<style type="text/css">
+  table.right { float: right; margin-left: 20px; }
+  table.right td { border: 1px solid #ccc; }
+</style>
+
+  </head>
+  <body>
+<div class="logo">
+  <a href="../index.html">
+    <img src="../_static/logo.png"
+         alt="LLVM Logo" width="250" height="88"/></a>
+</div>
+
+    <div class="related">
+      <h3>Navigation</h3>
+      <ul>
+        <li class="right" style="margin-right: 10px">
+          <a href="../genindex.html" title="General Index"
+             accesskey="I">index</a></li>
+        <li class="right" >
+          <a href="BuildingAJIT2.html" title="2. Building a JIT: Adding Optimizations – An introduction to ORC Layers"
+             accesskey="N">next</a> |</li>
+        <li class="right" >
+          <a href="OCamlLangImpl8.html" title="8. Kaleidoscope: Conclusion and other useful LLVM tidbits"
+             accesskey="P">previous</a> |</li>
+  <li><a href="http://llvm.org/">LLVM Home</a> | </li>
+  <li><a href="../index.html">Documentation</a>»</li>
+
+          <li><a href="index.html" accesskey="U">LLVM Tutorial: Table of Contents</a> »</li> 
+      </ul>
+    </div>
+
+
+    <div class="document">
+      <div class="documentwrapper">
+          <div class="body">
+            
+  <div class="section" id="building-a-jit-starting-out-with-kaleidoscopejit">
+<h1>1. Building a JIT: Starting out with KaleidoscopeJIT<a class="headerlink" href="#building-a-jit-starting-out-with-kaleidoscopejit" title="Permalink to this headline">¶</a></h1>
+<div class="contents local topic" id="contents">
+<ul class="simple">
+<li><a class="reference internal" href="#chapter-1-introduction" id="id11">Chapter 1 Introduction</a></li>
+<li><a class="reference internal" href="#jit-api-basics" id="id12">JIT API Basics</a></li>
+<li><a class="reference internal" href="#kaleidoscopejit" id="id13">KaleidoscopeJIT</a></li>
+<li><a class="reference internal" href="#full-code-listing" id="id14">Full Code Listing</a></li>
+</ul>
+</div>
+<div class="section" id="chapter-1-introduction">
+<h2><a class="toc-backref" href="#id11">1.1. Chapter 1 Introduction</a><a class="headerlink" href="#chapter-1-introduction" title="Permalink to this headline">¶</a></h2>
+<p>Welcome to Chapter 1 of the “Building an ORC-based JIT in LLVM” tutorial. This
+tutorial runs through the implementation of a JIT compiler using LLVM’s
+On-Request-Compilation (ORC) APIs. It begins with a simplified version of the
+KaleidoscopeJIT class used in the
+<a class="reference external" href="LangImpl1.html">Implementing a language with LLVM</a> tutorials and then
+introduces new features like optimization, lazy compilation and remote
+execution.</p>
+<p>The goal of this tutorial is to introduce you to LLVM’s ORC JIT APIs, show how
+these APIs interact with other parts of LLVM, and to teach you how to recombine
+them to build a custom JIT that is suited to your use-case.</p>
+<p>The structure of the tutorial is:</p>
+<ul class="simple">
+<li>Chapter #1: Investigate the simple KaleidoscopeJIT class. This will
+introduce some of the basic concepts of the ORC JIT APIs, including the
+idea of an ORC <em>Layer</em>.</li>
+<li><a class="reference external" href="BuildingAJIT2.html">Chapter #2</a>: Extend the basic KaleidoscopeJIT by adding
+a new layer that will optimize IR and generated code.</li>
+<li><a class="reference external" href="BuildingAJIT3.html">Chapter #3</a>: Further extend the JIT by adding a
+Compile-On-Demand layer to lazily compile IR.</li>
+<li><a class="reference external" href="BuildingAJIT4.html">Chapter #4</a>: Improve the laziness of our JIT by
+replacing the Compile-On-Demand layer with a custom layer that uses the ORC
+Compile Callbacks API directly to defer IR-generation until functions are
+called.</li>
+<li><a class="reference external" href="BuildingAJIT5.html">Chapter #5</a>: Add process isolation by JITing code into
+a remote process with reduced privileges using the JIT Remote APIs.</li>
+</ul>
+<p>To provide input for our JIT we will use the Kaleidoscope REPL from
+<a class="reference external" href="LangImpl7.html">Chapter 7</a> of the “Implementing a language in LLVM tutorial”,
+with one minor modification: We will remove the FunctionPassManager from the
+code for that chapter and replace it with optimization support in our JIT class
+in Chapter #2.</p>
+<p>Finally, a word on API generations: ORC is the 3rd generation of LLVM JIT API.
+It was preceded by MCJIT, and before that by the (now deleted) legacy JIT.
+These tutorials don’t assume any experience with these earlier APIs, but
+readers acquainted with them will see many familiar elements. Where appropriate
+we will make this connection with the earlier APIs explicit to help people who
+are transitioning from them to ORC.</p>
+</div>
+<div class="section" id="jit-api-basics">
+<h2><a class="toc-backref" href="#id12">1.2. JIT API Basics</a><a class="headerlink" href="#jit-api-basics" title="Permalink to this headline">¶</a></h2>
+<p>The purpose of a JIT compiler is to compile code “on-the-fly” as it is needed,
+rather than compiling whole programs to disk ahead of time as a traditional
+compiler does. To support that aim our initial, bare-bones JIT API will be:</p>
+<ol class="arabic simple">
+<li>Handle addModule(Module &M) – Make the given IR module available for
+execution.</li>
+<li>JITSymbol findSymbol(const std::string &Name) – Search for pointers to
+symbols (functions or variables) that have been added to the JIT.</li>
+<li>void removeModule(Handle H) – Remove a module from the JIT, releasing any
+memory that had been used for the compiled code.</li>
+</ol>
+<p>A basic use-case for this API, executing the ‘main’ function from a module,
+will look like:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span> <span class="n">M</span> <span class="o">=</span> <span class="n">buildModule</span><span class="p">();</span>
+<span class="n">JIT</span> <span class="n">J</span><span class="p">;</span>
+<span class="n">Handle</span> <span class="n">H</span> <span class="o">=</span> <span class="n">J</span><span class="p">.</span><span class="n">addModule</span><span class="p">(</span><span class="o">*</span><span class="n">M</span><span class="p">);</span>
+<span class="kt">int</span> <span class="p">(</span><span class="o">*</span><span class="n">Main</span><span class="p">)(</span><span class="kt">int</span><span class="p">,</span> <span class="kt">char</span><span class="o">*</span><span class="p">[])</span> <span class="o">=</span>
+  <span class="p">(</span><span class="kt">int</span><span class="p">(</span><span class="o">*</span><span class="p">)(</span><span class="kt">int</span><span class="p">,</span> <span class="kt">char</span><span class="o">*</span><span class="p">[])</span><span class="n">J</span><span class="p">.</span><span class="n">findSymbol</span><span class="p">(</span><span class="s">"main"</span><span class="p">).</span><span class="n">getAddress</span><span class="p">();</span>
+<span class="kt">int</span> <span class="n">Result</span> <span class="o">=</span> <span class="n">Main</span><span class="p">();</span>
+<span class="n">J</span><span class="p">.</span><span class="n">removeModule</span><span class="p">(</span><span class="n">H</span><span class="p">);</span>
+</pre></div>
+</div>
+<p>The APIs that we build in these tutorials will all be variations on this simple
+theme. Behind the API we will refine the implementation of the JIT to add
+support for optimization and lazy compilation. Eventually we will extend the
+API itself to allow higher-level program representations (e.g. ASTs) to be
+added to the JIT.</p>
+</div>
+<div class="section" id="kaleidoscopejit">
+<h2><a class="toc-backref" href="#id13">1.3. KaleidoscopeJIT</a><a class="headerlink" href="#kaleidoscopejit" title="Permalink to this headline">¶</a></h2>
+<p>In the previous section we described our API, now we examine a simple
+implementation of it: The KaleidoscopeJIT class <a class="footnote-reference" href="#id7" id="id1">[1]</a> that was used in the
+<a class="reference external" href="LangImpl1.html">Implementing a language with LLVM</a> tutorials. We will use
+the REPL code from <a class="reference external" href="LangImpl7.html">Chapter 7</a> of that tutorial to supply the
+input for our JIT: Each time the user enters an expression the REPL will add a
+new IR module containing the code for that expression to the JIT. If the
+expression is a top-level expression like ‘1+1’ or ‘sin(x)’, the REPL will also
+use the findSymbol method of our JIT class find and execute the code for the
+expression, and then use the removeModule method to remove the code again
+(since there’s no way to re-invoke an anonymous expression). In later chapters
+of this tutorial we’ll modify the REPL to enable new interactions with our JIT
+class, but for now we will take this setup for granted and focus our attention on
+the implementation of our JIT itself.</p>
+<p>Our KaleidoscopeJIT class is defined in the KaleidoscopeJIT.h header. After the
+usual include guards and #includes <a class="footnote-reference" href="#id8" id="id4">[2]</a>, we get to the definition of our class:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="cp">#ifndef LLVM_EXECUTIONENGINE_ORC_KALEIDOSCOPEJIT_H</span>
+<span class="cp">#define LLVM_EXECUTIONENGINE_ORC_KALEIDOSCOPEJIT_H</span>
+
+<span class="cp">#include "llvm/ExecutionEngine/ExecutionEngine.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/RTDyldMemoryManager.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/CompileUtils.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/IRCompileLayer.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/LambdaResolver.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/ObjectLinkingLayer.h"</span>
+<span class="cp">#include "llvm/IR/Mangler.h"</span>
+<span class="cp">#include "llvm/Support/DynamicLibrary.h"</span>
+
+<span class="k">namespace</span> <span class="n">llvm</span> <span class="p">{</span>
+<span class="k">namespace</span> <span class="n">orc</span> <span class="p">{</span>
+
+<span class="k">class</span> <span class="nc">KaleidoscopeJIT</span> <span class="p">{</span>
+<span class="nl">private:</span>
+
+  <span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">TargetMachine</span><span class="o">></span> <span class="n">TM</span><span class="p">;</span>
+  <span class="k">const</span> <span class="n">DataLayout</span> <span class="n">DL</span><span class="p">;</span>
+  <span class="n">ObjectLinkingLayer</span><span class="o"><></span> <span class="n">ObjectLayer</span><span class="p">;</span>
+  <span class="n">IRCompileLayer</span><span class="o"><</span><span class="n">decltype</span><span class="p">(</span><span class="n">ObjectLayer</span><span class="p">)</span><span class="o">></span> <span class="n">CompileLayer</span><span class="p">;</span>
+
+<span class="nl">public:</span>
+
+  <span class="k">typedef</span> <span class="n">decltype</span><span class="p">(</span><span class="n">CompileLayer</span><span class="p">)</span><span class="o">::</span><span class="n">ModuleSetHandleT</span> <span class="n">ModuleHandleT</span><span class="p">;</span>
+</pre></div>
+</div>
+<p>Our class begins with four members: A TargetMachine, TM, which will be used
+to build our LLVM compiler instance; A DataLayout, DL, which will be used for
+symbol mangling (more on that later), and two ORC <em>layers</em>: an
+ObjectLinkingLayer and a IRCompileLayer. We’ll be talking more about layers in
+the next chapter, but for now you can think of them as analogous to LLVM
+Passes: they wrap up useful JIT utilities behind an easy to compose interface.
+The first layer, ObjectLinkingLayer, is the foundation of our JIT: it takes
+in-memory object files produced by a compiler and links them on the fly to make
+them executable. This JIT-on-top-of-a-linker design was introduced in MCJIT,
+however the linker was hidden inside the MCJIT class. In ORC we expose the
+linker so that clients can access and configure it directly if they need to. In
+this tutorial our ObjectLinkingLayer will just be used to support the next layer
+in our stack: the IRCompileLayer, which will be responsible for taking LLVM IR,
+compiling it, and passing the resulting in-memory object files down to the
+object linking layer below.</p>
+<p>That’s it for member variables, after that we have a single typedef:
+ModuleHandle. This is the handle type that will be returned from our JIT’s
+addModule method, and can be passed to the removeModule method to remove a
+module. The IRCompileLayer class already provides a convenient handle type
+(IRCompileLayer::ModuleSetHandleT), so we just alias our ModuleHandle to this.</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="n">KaleidoscopeJIT</span><span class="p">()</span>
+    <span class="o">:</span> <span class="n">TM</span><span class="p">(</span><span class="n">EngineBuilder</span><span class="p">().</span><span class="n">selectTarget</span><span class="p">()),</span> <span class="n">DL</span><span class="p">(</span><span class="n">TM</span><span class="o">-></span><span class="n">createDataLayout</span><span class="p">()),</span>
+  <span class="n">CompileLayer</span><span class="p">(</span><span class="n">ObjectLayer</span><span class="p">,</span> <span class="n">SimpleCompiler</span><span class="p">(</span><span class="o">*</span><span class="n">TM</span><span class="p">))</span> <span class="p">{</span>
+  <span class="n">llvm</span><span class="o">::</span><span class="n">sys</span><span class="o">::</span><span class="n">DynamicLibrary</span><span class="o">::</span><span class="n">LoadLibraryPermanently</span><span class="p">(</span><span class="n">nullptr</span><span class="p">);</span>
+<span class="p">}</span>
+
+<span class="n">TargetMachine</span> <span class="o">&</span><span class="n">getTargetMachine</span><span class="p">()</span> <span class="p">{</span> <span class="k">return</span> <span class="o">*</span><span class="n">TM</span><span class="p">;</span> <span class="p">}</span>
+</pre></div>
+</div>
+<p>Next up we have our class constructor. We begin by initializing TM using the
+EngineBuilder::selectTarget helper method, which constructs a TargetMachine for
+the current process. Next we use our newly created TargetMachine to initialize
+DL, our DataLayout. Then we initialize our IRCompileLayer. Our IRCompile layer
+needs two things: (1) A reference to our object linking layer, and (2) a
+compiler instance to use to perform the actual compilation from IR to object
+files. We use the off-the-shelf SimpleCompiler instance for now. Finally, in
+the body of the constructor, we call the DynamicLibrary::LoadLibraryPermanently
+method with a nullptr argument. Normally the LoadLibraryPermanently method is
+called with the path of a dynamic library to load, but when passed a null
+pointer it will ‘load’ the host process itself, making its exported symbols
+available for execution.</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="n">ModuleHandle</span> <span class="nf">addModule</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span> <span class="n">M</span><span class="p">)</span> <span class="p">{</span>
+  <span class="c1">// Build our symbol resolver:</span>
+  <span class="c1">// Lambda 1: Look back into the JIT itself to find symbols that are part of</span>
+  <span class="c1">//           the same "logical dylib".</span>
+  <span class="c1">// Lambda 2: Search for external symbols in the host process.</span>
+  <span class="k">auto</span> <span class="n">Resolver</span> <span class="o">=</span> <span class="n">createLambdaResolver</span><span class="p">(</span>
+      <span class="p">[</span><span class="o">&</span><span class="p">](</span><span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="o">&</span><span class="n">Name</span><span class="p">)</span> <span class="p">{</span>
+        <span class="k">if</span> <span class="p">(</span><span class="k">auto</span> <span class="n">Sym</span> <span class="o">=</span> <span class="n">CompileLayer</span><span class="p">.</span><span class="n">findSymbol</span><span class="p">(</span><span class="n">Name</span><span class="p">,</span> <span class="nb">false</span><span class="p">))</span>
+          <span class="k">return</span> <span class="n">Sym</span><span class="p">.</span><span class="n">toRuntimeDyldSymbol</span><span class="p">();</span>
+        <span class="k">return</span> <span class="n">RuntimeDyld</span><span class="o">::</span><span class="n">SymbolInfo</span><span class="p">(</span><span class="n">nullptr</span><span class="p">);</span>
+      <span class="p">},</span>
+      <span class="p">[](</span><span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="o">&</span><span class="n">S</span><span class="p">)</span> <span class="p">{</span>
+        <span class="k">if</span> <span class="p">(</span><span class="k">auto</span> <span class="n">SymAddr</span> <span class="o">=</span>
+              <span class="n">RTDyldMemoryManager</span><span class="o">::</span><span class="n">getSymbolAddressInProcess</span><span class="p">(</span><span class="n">Name</span><span class="p">))</span>
+          <span class="k">return</span> <span class="n">RuntimeDyld</span><span class="o">::</span><span class="n">SymbolInfo</span><span class="p">(</span><span class="n">SymAddr</span><span class="p">,</span> <span class="n">JITSymbolFlags</span><span class="o">::</span><span class="n">Exported</span><span class="p">);</span>
+        <span class="k">return</span> <span class="n">RuntimeDyld</span><span class="o">::</span><span class="n">SymbolInfo</span><span class="p">(</span><span class="n">nullptr</span><span class="p">);</span>
+      <span class="p">});</span>
+
+  <span class="c1">// Build a singlton module set to hold our module.</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">vector</span><span class="o"><</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">>></span> <span class="n">Ms</span><span class="p">;</span>
+  <span class="n">Ms</span><span class="p">.</span><span class="n">push_back</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">M</span><span class="p">));</span>
+
+  <span class="c1">// Add the set to the JIT with the resolver we created above and a newly</span>
+  <span class="c1">// created SectionMemoryManager.</span>
+  <span class="k">return</span> <span class="n">CompileLayer</span><span class="p">.</span><span class="n">addModuleSet</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Ms</span><span class="p">),</span>
+                                   <span class="n">make_unique</span><span class="o"><</span><span class="n">SectionMemoryManager</span><span class="o">></span><span class="p">(),</span>
+                                   <span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Resolver</span><span class="p">));</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>Now we come to the first of our JIT API methods: addModule. This method is
+responsible for adding IR to the JIT and making it available for execution. In
+this initial implementation of our JIT we will make our modules “available for
+execution” by adding them straight to the IRCompileLayer, which will
+immediately compile them. In later chapters we will teach our JIT to be lazier
+and instead add the Modules to a “pending” list to be compiled if and when they
+are first executed.</p>
+<p>To add our module to the IRCompileLayer we need to supply two auxiliary objects
+(as well as the module itself): a memory manager and a symbol resolver.  The
+memory manager will be responsible for managing the memory allocated to JIT’d
+machine code, setting memory permissions, and registering exception handling
+tables (if the JIT’d code uses exceptions). For our memory manager we will use
+the SectionMemoryManager class: another off-the-shelf utility that provides all
+the basic functionality we need. The second auxiliary class, the symbol
+resolver, is more interesting for us. It exists to tell the JIT where to look
+when it encounters an <em>external symbol</em> in the module we are adding.  External
+symbols are any symbol not defined within the module itself, including calls to
+functions outside the JIT and calls to functions defined in other modules that
+have already been added to the JIT. It may seem as though modules added to the
+JIT should “know about one another” by default, but since we would still have to
+supply a symbol resolver for references to code outside the JIT it turns out to
+be easier to just re-use this one mechanism for all symbol resolution. This has
+the added benefit that the user has full control over the symbol resolution
+process. Should we search for definitions within the JIT first, then fall back
+on external definitions? Or should we prefer external definitions where
+available and only JIT code if we don’t already have an available
+implementation? By using a single symbol resolution scheme we are free to choose
+whatever makes the most sense for any given use case.</p>
+<p>Building a symbol resolver is made especially easy by the <em>createLambdaResolver</em>
+function. This function takes two lambdas <a class="footnote-reference" href="#id9" id="id5">[3]</a> and returns a
+RuntimeDyld::SymbolResolver instance. The first lambda is used as the
+implementation of the resolver’s findSymbolInLogicalDylib method, which searches
+for symbol definitions that should be thought of as being part of the same
+“logical” dynamic library as this Module. If you are familiar with static
+linking: this means that findSymbolInLogicalDylib should expose symbols with
+common linkage and hidden visibility. If all this sounds foreign you can ignore
+the details and just remember that this is the first method that the linker will
+use to try to find a symbol definition. If the findSymbolInLogicalDylib method
+returns a null result then the linker will call the second symbol resolver
+method, called findSymbol, which searches for symbols that should be thought of
+as external to (but visibile from) the module and its logical dylib. In this
+tutorial we will adopt the following simple scheme: All modules added to the JIT
+will behave as if they were linked into a single, ever-growing logical dylib. To
+implement this our first lambda (the one defining findSymbolInLogicalDylib) will
+just search for JIT’d code by calling the CompileLayer’s findSymbol method. If
+we don’t find a symbol in the JIT itself we’ll fall back to our second lambda,
+which implements findSymbol. This will use the
+RTDyldMemoyrManager::getSymbolAddressInProcess method to search for the symbol
+within the program itself. If we can’t find a symbol definition via either of
+these paths the JIT will refuse to accept our module, returning a “symbol not
+found” error.</p>
+<p>Now that we’ve built our symbol resolver we’re ready to add our module to the
+JIT. We do this by calling the CompileLayer’s addModuleSet method <a class="footnote-reference" href="#id10" id="id6">[4]</a>. Since
+we only have a single Module and addModuleSet expects a collection, we will
+create a vector of modules and add our module as the only member. Since we
+have already typedef’d our ModuleHandle type to be the same as the
+CompileLayer’s handle type, we can return the handle from addModuleSet
+directly from our addModule method.</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="n">JITSymbol</span> <span class="nf">findSymbol</span><span class="p">(</span><span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="n">Name</span><span class="p">)</span> <span class="p">{</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="n">MangledName</span><span class="p">;</span>
+  <span class="n">raw_string_ostream</span> <span class="n">MangledNameStream</span><span class="p">(</span><span class="n">MangledName</span><span class="p">);</span>
+  <span class="n">Mangler</span><span class="o">::</span><span class="n">getNameWithPrefix</span><span class="p">(</span><span class="n">MangledNameStream</span><span class="p">,</span> <span class="n">Name</span><span class="p">,</span> <span class="n">DL</span><span class="p">);</span>
+  <span class="k">return</span> <span class="n">CompileLayer</span><span class="p">.</span><span class="n">findSymbol</span><span class="p">(</span><span class="n">MangledNameStream</span><span class="p">.</span><span class="n">str</span><span class="p">(),</span> <span class="nb">true</span><span class="p">);</span>
+<span class="p">}</span>
+
+<span class="kt">void</span> <span class="nf">removeModule</span><span class="p">(</span><span class="n">ModuleHandle</span> <span class="n">H</span><span class="p">)</span> <span class="p">{</span>
+  <span class="n">CompileLayer</span><span class="p">.</span><span class="n">removeModuleSet</span><span class="p">(</span><span class="n">H</span><span class="p">);</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>Now that we can add code to our JIT, we need a way to find the symbols we’ve
+added to it. To do that we call the findSymbol method on our IRCompileLayer,
+but with a twist: We have to <em>mangle</em> the name of the symbol we’re searching
+for first. The reason for this is that the ORC JIT components use mangled
+symbols internally the same way a static compiler and linker would, rather
+than using plain IR symbol names. The kind of mangling will depend on the
+DataLayout, which in turn depends on the target platform. To allow us to
+remain portable and search based on the un-mangled name, we just re-produce
+this mangling ourselves.</p>
+<p>We now come to the last method in our JIT API: removeModule. This method is
+responsible for destructing the MemoryManager and SymbolResolver that were
+added with a given module, freeing any resources they were using in the
+process. In our Kaleidoscope demo we rely on this method to remove the module
+representing the most recent top-level expression, preventing it from being
+treated as a duplicate definition when the next top-level expression is
+entered. It is generally good to free any module that you know you won’t need
+to call further, just to free up the resources dedicated to it. However, you
+don’t strictly need to do this: All resources will be cleaned up when your
+JIT class is destructed, if the haven’t been freed before then.</p>
+<p>This brings us to the end of Chapter 1 of Building a JIT. You now have a basic
+but fully functioning JIT stack that you can use to take LLVM IR and make it
+executable within the context of your JIT process. In the next chapter we’ll
+look at how to extend this JIT to produce better quality code, and in the
+process take a deeper look at the ORC layer concept.</p>
+<p><a class="reference external" href="BuildingAJIT2.html">Next: Extending the KaleidoscopeJIT</a></p>
+</div>
+<div class="section" id="full-code-listing">
+<h2><a class="toc-backref" href="#id14">1.4. Full Code Listing</a><a class="headerlink" href="#full-code-listing" title="Permalink to this headline">¶</a></h2>
+<p>Here is the complete code listing for our running example. To build this
+example, use:</p>
+<div class="highlight-bash"><div class="highlight"><pre><span class="c"># Compile</span>
+clang++ -g toy.cpp <span class="sb">`</span>llvm-config --cxxflags --ldflags --system-libs --libs core orc native<span class="sb">`</span> -O3 -o toy
+<span class="c"># Run</span>
+./toy
+</pre></div>
+</div>
+<p>Here is the code:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">//===----- KaleidoscopeJIT.h - A simple JIT for Kaleidoscope ----*- C++ -*-===//</span>
+<span class="c1">//</span>
+<span class="c1">//                     The LLVM Compiler Infrastructure</span>
+<span class="c1">//</span>
+<span class="c1">// This file is distributed under the University of Illinois Open Source</span>
+<span class="c1">// License. See LICENSE.TXT for details.</span>
+<span class="c1">//</span>
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+<span class="c1">//</span>
+<span class="c1">// Contains a simple JIT definition for use in the kaleidoscope tutorials.</span>
+<span class="c1">//</span>
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+
+<span class="cp">#ifndef LLVM_EXECUTIONENGINE_ORC_KALEIDOSCOPEJIT_H</span>
+<span class="cp">#define LLVM_EXECUTIONENGINE_ORC_KALEIDOSCOPEJIT_H</span>
+
+<span class="cp">#include "llvm/ADT/STLExtras.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/ExecutionEngine.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/RuntimeDyld.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/SectionMemoryManager.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/CompileUtils.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/JITSymbol.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/IRCompileLayer.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/LambdaResolver.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/ObjectLinkingLayer.h"</span>
+<span class="cp">#include "llvm/IR/DataLayout.h"</span>
+<span class="cp">#include "llvm/IR/Mangler.h"</span>
+<span class="cp">#include "llvm/Support/DynamicLibrary.h"</span>
+<span class="cp">#include "llvm/Support/raw_ostream.h"</span>
+<span class="cp">#include "llvm/Target/TargetMachine.h"</span>
+<span class="cp">#include <algorithm></span>
+<span class="cp">#include <memory></span>
+<span class="cp">#include <string></span>
+<span class="cp">#include <vector></span>
+
+<span class="k">namespace</span> <span class="n">llvm</span> <span class="p">{</span>
+<span class="k">namespace</span> <span class="n">orc</span> <span class="p">{</span>
+
+<span class="k">class</span> <span class="nc">KaleidoscopeJIT</span> <span class="p">{</span>
+<span class="nl">private:</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">TargetMachine</span><span class="o">></span> <span class="n">TM</span><span class="p">;</span>
+  <span class="k">const</span> <span class="n">DataLayout</span> <span class="n">DL</span><span class="p">;</span>
+  <span class="n">ObjectLinkingLayer</span><span class="o"><></span> <span class="n">ObjectLayer</span><span class="p">;</span>
+  <span class="n">IRCompileLayer</span><span class="o"><</span><span class="n">decltype</span><span class="p">(</span><span class="n">ObjectLayer</span><span class="p">)</span><span class="o">></span> <span class="n">CompileLayer</span><span class="p">;</span>
+
+<span class="nl">public:</span>
+  <span class="k">typedef</span> <span class="n">decltype</span><span class="p">(</span><span class="n">CompileLayer</span><span class="p">)</span><span class="o">::</span><span class="n">ModuleSetHandleT</span> <span class="n">ModuleHandle</span><span class="p">;</span>
+
+  <span class="n">KaleidoscopeJIT</span><span class="p">()</span>
+      <span class="o">:</span> <span class="n">TM</span><span class="p">(</span><span class="n">EngineBuilder</span><span class="p">().</span><span class="n">selectTarget</span><span class="p">()),</span> <span class="n">DL</span><span class="p">(</span><span class="n">TM</span><span class="o">-></span><span class="n">createDataLayout</span><span class="p">()),</span>
+        <span class="n">CompileLayer</span><span class="p">(</span><span class="n">ObjectLayer</span><span class="p">,</span> <span class="n">SimpleCompiler</span><span class="p">(</span><span class="o">*</span><span class="n">TM</span><span class="p">))</span> <span class="p">{</span>
+    <span class="n">llvm</span><span class="o">::</span><span class="n">sys</span><span class="o">::</span><span class="n">DynamicLibrary</span><span class="o">::</span><span class="n">LoadLibraryPermanently</span><span class="p">(</span><span class="n">nullptr</span><span class="p">);</span>
+  <span class="p">}</span>
+
+  <span class="n">TargetMachine</span> <span class="o">&</span><span class="n">getTargetMachine</span><span class="p">()</span> <span class="p">{</span> <span class="k">return</span> <span class="o">*</span><span class="n">TM</span><span class="p">;</span> <span class="p">}</span>
+
+  <span class="n">ModuleHandle</span> <span class="n">addModule</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span> <span class="n">M</span><span class="p">)</span> <span class="p">{</span>
+    <span class="c1">// Build our symbol resolver:</span>
+    <span class="c1">// Lambda 1: Look back into the JIT itself to find symbols that are part of</span>
+    <span class="c1">//           the same "logical dylib".</span>
+    <span class="c1">// Lambda 2: Search for external symbols in the host process.</span>
+    <span class="k">auto</span> <span class="n">Resolver</span> <span class="o">=</span> <span class="n">createLambdaResolver</span><span class="p">(</span>
+        <span class="p">[</span><span class="o">&</span><span class="p">](</span><span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="o">&</span><span class="n">Name</span><span class="p">)</span> <span class="p">{</span>
+          <span class="k">if</span> <span class="p">(</span><span class="k">auto</span> <span class="n">Sym</span> <span class="o">=</span> <span class="n">CompileLayer</span><span class="p">.</span><span class="n">findSymbol</span><span class="p">(</span><span class="n">Name</span><span class="p">,</span> <span class="nb">false</span><span class="p">))</span>
+            <span class="k">return</span> <span class="n">Sym</span><span class="p">.</span><span class="n">toRuntimeDyldSymbol</span><span class="p">();</span>
+          <span class="k">return</span> <span class="n">RuntimeDyld</span><span class="o">::</span><span class="n">SymbolInfo</span><span class="p">(</span><span class="n">nullptr</span><span class="p">);</span>
+        <span class="p">},</span>
+        <span class="p">[](</span><span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="o">&</span><span class="n">Name</span><span class="p">)</span> <span class="p">{</span>
+          <span class="k">if</span> <span class="p">(</span><span class="k">auto</span> <span class="n">SymAddr</span> <span class="o">=</span>
+                <span class="n">RTDyldMemoryManager</span><span class="o">::</span><span class="n">getSymbolAddressInProcess</span><span class="p">(</span><span class="n">Name</span><span class="p">))</span>
+            <span class="k">return</span> <span class="n">RuntimeDyld</span><span class="o">::</span><span class="n">SymbolInfo</span><span class="p">(</span><span class="n">SymAddr</span><span class="p">,</span> <span class="n">JITSymbolFlags</span><span class="o">::</span><span class="n">Exported</span><span class="p">);</span>
+          <span class="k">return</span> <span class="n">RuntimeDyld</span><span class="o">::</span><span class="n">SymbolInfo</span><span class="p">(</span><span class="n">nullptr</span><span class="p">);</span>
+        <span class="p">});</span>
+
+    <span class="c1">// Build a singlton module set to hold our module.</span>
+    <span class="n">std</span><span class="o">::</span><span class="n">vector</span><span class="o"><</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">>></span> <span class="n">Ms</span><span class="p">;</span>
+    <span class="n">Ms</span><span class="p">.</span><span class="n">push_back</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">M</span><span class="p">));</span>
+
+    <span class="c1">// Add the set to the JIT with the resolver we created above and a newly</span>
+    <span class="c1">// created SectionMemoryManager.</span>
+    <span class="k">return</span> <span class="n">CompileLayer</span><span class="p">.</span><span class="n">addModuleSet</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Ms</span><span class="p">),</span>
+                                     <span class="n">make_unique</span><span class="o"><</span><span class="n">SectionMemoryManager</span><span class="o">></span><span class="p">(),</span>
+                                     <span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Resolver</span><span class="p">));</span>
+  <span class="p">}</span>
+
+  <span class="n">JITSymbol</span> <span class="n">findSymbol</span><span class="p">(</span><span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="n">Name</span><span class="p">)</span> <span class="p">{</span>
+    <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="n">MangledName</span><span class="p">;</span>
+    <span class="n">raw_string_ostream</span> <span class="nf">MangledNameStream</span><span class="p">(</span><span class="n">MangledName</span><span class="p">);</span>
+    <span class="n">Mangler</span><span class="o">::</span><span class="n">getNameWithPrefix</span><span class="p">(</span><span class="n">MangledNameStream</span><span class="p">,</span> <span class="n">Name</span><span class="p">,</span> <span class="n">DL</span><span class="p">);</span>
+    <span class="k">return</span> <span class="n">CompileLayer</span><span class="p">.</span><span class="n">findSymbol</span><span class="p">(</span><span class="n">MangledNameStream</span><span class="p">.</span><span class="n">str</span><span class="p">(),</span> <span class="nb">true</span><span class="p">);</span>
+  <span class="p">}</span>
+
+  <span class="kt">void</span> <span class="n">removeModule</span><span class="p">(</span><span class="n">ModuleHandle</span> <span class="n">H</span><span class="p">)</span> <span class="p">{</span>
+    <span class="n">CompileLayer</span><span class="p">.</span><span class="n">removeModuleSet</span><span class="p">(</span><span class="n">H</span><span class="p">);</span>
+  <span class="p">}</span>
+
+<span class="p">};</span>
+
+<span class="p">}</span> <span class="c1">// end namespace orc</span>
+<span class="p">}</span> <span class="c1">// end namespace llvm</span>
+
+<span class="cp">#endif </span><span class="c1">// LLVM_EXECUTIONENGINE_ORC_KALEIDOSCOPEJIT_H</span>
+</pre></div>
+</div>
+<table class="docutils footnote" frame="void" id="id7" rules="none">
+<colgroup><col class="label" /><col /></colgroup>
+<tbody valign="top">
+<tr><td class="label"><a class="fn-backref" href="#id1">[1]</a></td><td>Actually we use a cut-down version of KaleidoscopeJIT that makes a
+simplifying assumption: symbols cannot be re-defined. This will make it
+impossible to re-define symbols in the REPL, but will make our symbol
+lookup logic simpler. Re-introducing support for symbol redefinition is
+left as an exercise for the reader. (The KaleidoscopeJIT.h used in the
+original tutorials will be a helpful reference).</td></tr>
+</tbody>
+</table>
+<table class="docutils footnote" frame="void" id="id8" rules="none">
+<colgroup><col class="label" /><col /></colgroup>
+<tbody valign="top">
+<tr><td class="label"><a class="fn-backref" href="#id4">[2]</a></td><td><table border="1" class="first last docutils">
+<colgroup>
+<col width="33%" />
+<col width="67%" />
+</colgroup>
+<thead valign="bottom">
+<tr class="row-odd"><th class="head">File</th>
+<th class="head">Reason for inclusion</th>
+</tr>
+</thead>
+<tbody valign="top">
+<tr class="row-even"><td>ExecutionEngine.h</td>
+<td>Access to the EngineBuilder::selectTarget
+method.</td>
+</tr>
+<tr class="row-odd"><td>RTDyldMemoryManager.h</td>
+<td>Access to the
+RTDyldMemoryManager::getSymbolAddressInProcess
+method.</td>
+</tr>
+<tr class="row-even"><td>CompileUtils.h</td>
+<td>Provides the SimpleCompiler class.</td>
+</tr>
+<tr class="row-odd"><td>IRCompileLayer.h</td>
+<td>Provides the IRCompileLayer class.</td>
+</tr>
+<tr class="row-even"><td>LambdaResolver.h</td>
+<td>Access the createLambdaResolver function,
+which provides easy construction of symbol
+resolvers.</td>
+</tr>
+<tr class="row-odd"><td>ObjectLinkingLayer.h</td>
+<td>Provides the ObjectLinkingLayer class.</td>
+</tr>
+<tr class="row-even"><td>Mangler.h</td>
+<td>Provides the Mangler class for platform
+specific name-mangling.</td>
+</tr>
+<tr class="row-odd"><td>DynamicLibrary.h</td>
+<td>Provides the DynamicLibrary class, which
+makes symbols in the host process searchable.</td>
+</tr>
+</tbody>
+</table>
+</td></tr>
+</tbody>
+</table>
+<table class="docutils footnote" frame="void" id="id9" rules="none">
+<colgroup><col class="label" /><col /></colgroup>
+<tbody valign="top">
+<tr><td class="label"><a class="fn-backref" href="#id5">[3]</a></td><td>Actually they don’t have to be lambdas, any object with a call operator
+will do, including plain old functions or std::functions.</td></tr>
+</tbody>
+</table>
+<table class="docutils footnote" frame="void" id="id10" rules="none">
+<colgroup><col class="label" /><col /></colgroup>
+<tbody valign="top">
+<tr><td class="label"><a class="fn-backref" href="#id6">[4]</a></td><td>ORC layers accept sets of Modules, rather than individual ones, so that
+all Modules in the set could be co-located by the memory manager, though
+this feature is not yet implemented.</td></tr>
+</tbody>
+</table>
+</div>
+</div>
+
+
+          </div>
+      </div>
+      <div class="clearer"></div>
+    </div>
+    <div class="related">
+      <h3>Navigation</h3>
+      <ul>
+        <li class="right" style="margin-right: 10px">
+          <a href="../genindex.html" title="General Index"
+             >index</a></li>
+        <li class="right" >
+          <a href="BuildingAJIT2.html" title="2. Building a JIT: Adding Optimizations – An introduction to ORC Layers"
+             >next</a> |</li>
+        <li class="right" >
+          <a href="OCamlLangImpl8.html" title="8. Kaleidoscope: Conclusion and other useful LLVM tidbits"
+             >previous</a> |</li>
+  <li><a href="http://llvm.org/">LLVM Home</a> | </li>
+  <li><a href="../index.html">Documentation</a>»</li>
+
+          <li><a href="index.html" >LLVM Tutorial: Table of Contents</a> »</li> 
+      </ul>
+    </div>
+    <div class="footer">
+        © Copyright 2003-2016, LLVM Project.
+      Last updated on 2016-12-21.
+      Created using <a href="http://sphinx-doc.org/">Sphinx</a> 1.2.2.
+    </div>
+  </body>
+</html>
\ No newline at end of file

Added: www-releases/trunk/3.9.1/docs/tutorial/BuildingAJIT2.html
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/tutorial/BuildingAJIT2.html?rev=290368&view=auto
==============================================================================
--- www-releases/trunk/3.9.1/docs/tutorial/BuildingAJIT2.html (added)
+++ www-releases/trunk/3.9.1/docs/tutorial/BuildingAJIT2.html Thu Dec 22 14:04:03 2016
@@ -0,0 +1,565 @@
+
+<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN"
+  "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd">
+
+
+<html xmlns="http://www.w3.org/1999/xhtml">
+  <head>
+    <meta http-equiv="Content-Type" content="text/html; charset=utf-8" />
+    
+    <title>2. Building a JIT: Adding Optimizations – An introduction to ORC Layers — LLVM 3.9 documentation</title>
+    
+    <link rel="stylesheet" href="../_static/llvm-theme.css" type="text/css" />
+    <link rel="stylesheet" href="../_static/pygments.css" type="text/css" />
+    
+    <script type="text/javascript">
+      var DOCUMENTATION_OPTIONS = {
+        URL_ROOT:    '../',
+        VERSION:     '3.9',
+        COLLAPSE_INDEX: false,
+        FILE_SUFFIX: '.html',
+        HAS_SOURCE:  true
+      };
+    </script>
+    <script type="text/javascript" src="../_static/jquery.js"></script>
+    <script type="text/javascript" src="../_static/underscore.js"></script>
+    <script type="text/javascript" src="../_static/doctools.js"></script>
+    <link rel="top" title="LLVM 3.9 documentation" href="../index.html" />
+    <link rel="up" title="LLVM Tutorial: Table of Contents" href="index.html" />
+    <link rel="next" title="3. Building a JIT: Per-function Lazy Compilation" href="BuildingAJIT3.html" />
+    <link rel="prev" title="1. Building a JIT: Starting out with KaleidoscopeJIT" href="BuildingAJIT1.html" />
+<style type="text/css">
+  table.right { float: right; margin-left: 20px; }
+  table.right td { border: 1px solid #ccc; }
+</style>
+
+  </head>
+  <body>
+<div class="logo">
+  <a href="../index.html">
+    <img src="../_static/logo.png"
+         alt="LLVM Logo" width="250" height="88"/></a>
+</div>
+
+    <div class="related">
+      <h3>Navigation</h3>
+      <ul>
+        <li class="right" style="margin-right: 10px">
+          <a href="../genindex.html" title="General Index"
+             accesskey="I">index</a></li>
+        <li class="right" >
+          <a href="BuildingAJIT3.html" title="3. Building a JIT: Per-function Lazy Compilation"
+             accesskey="N">next</a> |</li>
+        <li class="right" >
+          <a href="BuildingAJIT1.html" title="1. Building a JIT: Starting out with KaleidoscopeJIT"
+             accesskey="P">previous</a> |</li>
+  <li><a href="http://llvm.org/">LLVM Home</a> | </li>
+  <li><a href="../index.html">Documentation</a>»</li>
+
+          <li><a href="index.html" accesskey="U">LLVM Tutorial: Table of Contents</a> »</li> 
+      </ul>
+    </div>
+
+
+    <div class="document">
+      <div class="documentwrapper">
+          <div class="body">
+            
+  <div class="section" id="building-a-jit-adding-optimizations-an-introduction-to-orc-layers">
+<h1>2. Building a JIT: Adding Optimizations – An introduction to ORC Layers<a class="headerlink" href="#building-a-jit-adding-optimizations-an-introduction-to-orc-layers" title="Permalink to this headline">¶</a></h1>
+<div class="contents local topic" id="contents">
+<ul class="simple">
+<li><a class="reference internal" href="#chapter-2-introduction" id="id4">Chapter 2 Introduction</a></li>
+<li><a class="reference internal" href="#optimizing-modules-using-the-irtransformlayer" id="id5">Optimizing Modules using the IRTransformLayer</a></li>
+<li><a class="reference internal" href="#full-code-listing" id="id6">Full Code Listing</a></li>
+</ul>
+</div>
+<p><strong>This tutorial is under active development. It is incomplete and details may
+change frequently.</strong> Nonetheless we invite you to try it out as it stands, and
+we welcome any feedback.</p>
+<div class="section" id="chapter-2-introduction">
+<h2><a class="toc-backref" href="#id4">2.1. Chapter 2 Introduction</a><a class="headerlink" href="#chapter-2-introduction" title="Permalink to this headline">¶</a></h2>
+<p>Welcome to Chapter 2 of the “Building an ORC-based JIT in LLVM” tutorial. In
+<a class="reference external" href="BuildingAJIT1.html">Chapter 1</a> of this series we examined a basic JIT
+class, KaleidoscopeJIT, that could take LLVM IR modules as input and produce
+executable code in memory. KaleidoscopeJIT was able to do this with relatively
+little code by composing two off-the-shelf <em>ORC layers</em>: IRCompileLayer and
+ObjectLinkingLayer, to do much of the heavy lifting.</p>
+<p>In this layer we’ll learn more about the ORC layer concept by using a new layer,
+IRTransformLayer, to add IR optimization support to KaleidoscopeJIT.</p>
+</div>
+<div class="section" id="optimizing-modules-using-the-irtransformlayer">
+<h2><a class="toc-backref" href="#id5">2.2. Optimizing Modules using the IRTransformLayer</a><a class="headerlink" href="#optimizing-modules-using-the-irtransformlayer" title="Permalink to this headline">¶</a></h2>
+<p>In <a class="reference external" href="LangImpl4.html">Chapter 4</a> of the “Implementing a language with LLVM”
+tutorial series the llvm <em>FunctionPassManager</em> is introduced as a means for
+optimizing LLVM IR. Interested readers may read that chapter for details, but
+in short: to optimize a Module we create an llvm::FunctionPassManager
+instance, configure it with a set of optimizations, then run the PassManager on
+a Module to mutate it into a (hopefully) more optimized but semantically
+equivalent form. In the original tutorial series the FunctionPassManager was
+created outside the KaleidoscopeJIT and modules were optimized before being
+added to it. In this Chapter we will make optimization a phase of our JIT
+instead. For now this will provide us a motivation to learn more about ORC
+layers, but in the long term making optimization part of our JIT will yield an
+important benefit: When we begin lazily compiling code (i.e. deferring
+compilation of each function until the first time it’s run), having
+optimization managed by our JIT will allow us to optimize lazily too, rather
+than having to do all our optimization up-front.</p>
+<p>To add optimization support to our JIT we will take the KaleidoscopeJIT from
+Chapter 1 and compose an ORC <em>IRTransformLayer</em> on top. We will look at how the
+IRTransformLayer works in more detail below, but the interface is simple: the
+constructor for this layer takes a reference to the layer below (as all layers
+do) plus an <em>IR optimization function</em> that it will apply to each Module that
+is added via addModuleSet:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="k">class</span> <span class="nc">KaleidoscopeJIT</span> <span class="p">{</span>
+<span class="nl">private:</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">TargetMachine</span><span class="o">></span> <span class="n">TM</span><span class="p">;</span>
+  <span class="k">const</span> <span class="n">DataLayout</span> <span class="n">DL</span><span class="p">;</span>
+  <span class="n">ObjectLinkingLayer</span><span class="o"><></span> <span class="n">ObjectLayer</span><span class="p">;</span>
+  <span class="n">IRCompileLayer</span><span class="o"><</span><span class="n">decltype</span><span class="p">(</span><span class="n">ObjectLayer</span><span class="p">)</span><span class="o">></span> <span class="n">CompileLayer</span><span class="p">;</span>
+
+  <span class="k">typedef</span> <span class="n">std</span><span class="o">::</span><span class="n">function</span><span class="o"><</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span><span class="p">)</span><span class="o">></span>
+    <span class="n">OptimizeFunction</span><span class="p">;</span>
+
+  <span class="n">IRTransformLayer</span><span class="o"><</span><span class="n">decltype</span><span class="p">(</span><span class="n">CompileLayer</span><span class="p">),</span> <span class="n">OptimizeFunction</span><span class="o">></span> <span class="n">OptimizeLayer</span><span class="p">;</span>
+
+<span class="nl">public:</span>
+  <span class="k">typedef</span> <span class="n">decltype</span><span class="p">(</span><span class="n">OptimizeLayer</span><span class="p">)</span><span class="o">::</span><span class="n">ModuleSetHandleT</span> <span class="n">ModuleHandle</span><span class="p">;</span>
+
+  <span class="n">KaleidoscopeJIT</span><span class="p">()</span>
+      <span class="o">:</span> <span class="n">TM</span><span class="p">(</span><span class="n">EngineBuilder</span><span class="p">().</span><span class="n">selectTarget</span><span class="p">()),</span> <span class="n">DL</span><span class="p">(</span><span class="n">TM</span><span class="o">-></span><span class="n">createDataLayout</span><span class="p">()),</span>
+        <span class="n">CompileLayer</span><span class="p">(</span><span class="n">ObjectLayer</span><span class="p">,</span> <span class="n">SimpleCompiler</span><span class="p">(</span><span class="o">*</span><span class="n">TM</span><span class="p">)),</span>
+        <span class="n">OptimizeLayer</span><span class="p">(</span><span class="n">CompileLayer</span><span class="p">,</span>
+                      <span class="p">[</span><span class="k">this</span><span class="p">](</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span> <span class="n">M</span><span class="p">)</span> <span class="p">{</span>
+                        <span class="k">return</span> <span class="n">optimizeModule</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">M</span><span class="p">));</span>
+                      <span class="p">})</span> <span class="p">{</span>
+    <span class="n">llvm</span><span class="o">::</span><span class="n">sys</span><span class="o">::</span><span class="n">DynamicLibrary</span><span class="o">::</span><span class="n">LoadLibraryPermanently</span><span class="p">(</span><span class="n">nullptr</span><span class="p">);</span>
+  <span class="p">}</span>
+</pre></div>
+</div>
+<p>Our extended KaleidoscopeJIT class starts out the same as it did in Chapter 1,
+but after the CompileLayer we introduce a typedef for our optimization function.
+In this case we use a std::function (a handy wrapper for “function-like” things)
+from a single unique_ptr<Module> input to a std::unique_ptr<Module> output. With
+our optimization function typedef in place we can declare our OptimizeLayer,
+which sits on top of our CompileLayer.</p>
+<p>To initialize our OptimizeLayer we pass it a reference to the CompileLayer
+below (standard practice for layers), and we initialize the OptimizeFunction
+using a lambda that calls out to an “optimizeModule” function that we will
+define below.</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">// ...</span>
+<span class="k">auto</span> <span class="n">Resolver</span> <span class="o">=</span> <span class="n">createLambdaResolver</span><span class="p">(</span>
+    <span class="p">[</span><span class="o">&</span><span class="p">](</span><span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="o">&</span><span class="n">Name</span><span class="p">)</span> <span class="p">{</span>
+      <span class="k">if</span> <span class="p">(</span><span class="k">auto</span> <span class="n">Sym</span> <span class="o">=</span> <span class="n">OptimizeLayer</span><span class="p">.</span><span class="n">findSymbol</span><span class="p">(</span><span class="n">Name</span><span class="p">,</span> <span class="nb">false</span><span class="p">))</span>
+        <span class="k">return</span> <span class="n">Sym</span><span class="p">.</span><span class="n">toRuntimeDyldSymbol</span><span class="p">();</span>
+      <span class="k">return</span> <span class="n">RuntimeDyld</span><span class="o">::</span><span class="n">SymbolInfo</span><span class="p">(</span><span class="n">nullptr</span><span class="p">);</span>
+    <span class="p">},</span>
+<span class="c1">// ...</span>
+</pre></div>
+</div>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">// ...</span>
+<span class="k">return</span> <span class="n">OptimizeLayer</span><span class="p">.</span><span class="n">addModuleSet</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Ms</span><span class="p">),</span>
+                                  <span class="n">make_unique</span><span class="o"><</span><span class="n">SectionMemoryManager</span><span class="o">></span><span class="p">(),</span>
+                                  <span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Resolver</span><span class="p">));</span>
+<span class="c1">// ...</span>
+</pre></div>
+</div>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">// ...</span>
+<span class="k">return</span> <span class="n">OptimizeLayer</span><span class="p">.</span><span class="n">findSymbol</span><span class="p">(</span><span class="n">MangledNameStream</span><span class="p">.</span><span class="n">str</span><span class="p">(),</span> <span class="nb">true</span><span class="p">);</span>
+<span class="c1">// ...</span>
+</pre></div>
+</div>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">// ...</span>
+<span class="n">OptimizeLayer</span><span class="p">.</span><span class="n">removeModuleSet</span><span class="p">(</span><span class="n">H</span><span class="p">);</span>
+<span class="c1">// ...</span>
+</pre></div>
+</div>
+<p>Next we need to replace references to ‘CompileLayer’ with references to
+OptimizeLayer in our key methods: addModule, findSymbol, and removeModule. In
+addModule we need to be careful to replace both references: the findSymbol call
+inside our resolver, and the call through to addModuleSet.</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span> <span class="n">optimizeModule</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span> <span class="n">M</span><span class="p">)</span> <span class="p">{</span>
+  <span class="c1">// Create a function pass manager.</span>
+  <span class="k">auto</span> <span class="n">FPM</span> <span class="o">=</span> <span class="n">llvm</span><span class="o">::</span><span class="n">make_unique</span><span class="o"><</span><span class="n">legacy</span><span class="o">::</span><span class="n">FunctionPassManager</span><span class="o">></span><span class="p">(</span><span class="n">M</span><span class="p">.</span><span class="n">get</span><span class="p">());</span>
+
+  <span class="c1">// Add some optimizations.</span>
+  <span class="n">FPM</span><span class="o">-></span><span class="n">add</span><span class="p">(</span><span class="n">createInstructionCombiningPass</span><span class="p">());</span>
+  <span class="n">FPM</span><span class="o">-></span><span class="n">add</span><span class="p">(</span><span class="n">createReassociatePass</span><span class="p">());</span>
+  <span class="n">FPM</span><span class="o">-></span><span class="n">add</span><span class="p">(</span><span class="n">createGVNPass</span><span class="p">());</span>
+  <span class="n">FPM</span><span class="o">-></span><span class="n">add</span><span class="p">(</span><span class="n">createCFGSimplificationPass</span><span class="p">());</span>
+  <span class="n">FPM</span><span class="o">-></span><span class="n">doInitialization</span><span class="p">();</span>
+
+  <span class="c1">// Run the optimizations over all functions in the module being added to</span>
+  <span class="c1">// the JIT.</span>
+  <span class="k">for</span> <span class="p">(</span><span class="k">auto</span> <span class="o">&</span><span class="n">F</span> <span class="o">:</span> <span class="o">*</span><span class="n">M</span><span class="p">)</span>
+    <span class="n">FPM</span><span class="o">-></span><span class="n">run</span><span class="p">(</span><span class="n">F</span><span class="p">);</span>
+
+  <span class="k">return</span> <span class="n">M</span><span class="p">;</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>At the bottom of our JIT we add a private method to do the actual optimization:
+<em>optimizeModule</em>. This function sets up a FunctionPassManager, adds some passes
+to it, runs it over every function in the module, and then returns the mutated
+module. The specific optimizations are the same ones used in
+<a class="reference external" href="LangImpl4.html">Chapter 4</a> of the “Implementing a language with LLVM”
+tutorial series. Readers may visit that chapter for a more in-depth
+discussion of these, and of IR optimization in general.</p>
+<p>And that’s it in terms of changes to KaleidoscopeJIT: When a module is added via
+addModule the OptimizeLayer will call our optimizeModule function before passing
+the transformed module on to the CompileLayer below. Of course, we could have
+called optimizeModule directly in our addModule function and not gone to the
+bother of using the IRTransformLayer, but doing so gives us another opportunity
+to see how layers compose. It also provides a neat entry point to the <em>layer</em>
+concept itself, because IRTransformLayer turns out to be one of the simplest
+implementations of the layer concept that can be devised:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="k">template</span> <span class="o"><</span><span class="k">typename</span> <span class="n">BaseLayerT</span><span class="p">,</span> <span class="k">typename</span> <span class="n">TransformFtor</span><span class="o">></span>
+<span class="k">class</span> <span class="nc">IRTransformLayer</span> <span class="p">{</span>
+<span class="nl">public:</span>
+  <span class="k">typedef</span> <span class="k">typename</span> <span class="n">BaseLayerT</span><span class="o">::</span><span class="n">ModuleSetHandleT</span> <span class="n">ModuleSetHandleT</span><span class="p">;</span>
+
+  <span class="n">IRTransformLayer</span><span class="p">(</span><span class="n">BaseLayerT</span> <span class="o">&</span><span class="n">BaseLayer</span><span class="p">,</span>
+                   <span class="n">TransformFtor</span> <span class="n">Transform</span> <span class="o">=</span> <span class="n">TransformFtor</span><span class="p">())</span>
+    <span class="o">:</span> <span class="n">BaseLayer</span><span class="p">(</span><span class="n">BaseLayer</span><span class="p">),</span> <span class="n">Transform</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Transform</span><span class="p">))</span> <span class="p">{}</span>
+
+  <span class="k">template</span> <span class="o"><</span><span class="k">typename</span> <span class="n">ModuleSetT</span><span class="p">,</span> <span class="k">typename</span> <span class="n">MemoryManagerPtrT</span><span class="p">,</span>
+            <span class="k">typename</span> <span class="n">SymbolResolverPtrT</span><span class="o">></span>
+  <span class="n">ModuleSetHandleT</span> <span class="n">addModuleSet</span><span class="p">(</span><span class="n">ModuleSetT</span> <span class="n">Ms</span><span class="p">,</span>
+                                <span class="n">MemoryManagerPtrT</span> <span class="n">MemMgr</span><span class="p">,</span>
+                                <span class="n">SymbolResolverPtrT</span> <span class="n">Resolver</span><span class="p">)</span> <span class="p">{</span>
+
+    <span class="k">for</span> <span class="p">(</span><span class="k">auto</span> <span class="n">I</span> <span class="o">=</span> <span class="n">Ms</span><span class="p">.</span><span class="n">begin</span><span class="p">(),</span> <span class="n">E</span> <span class="o">=</span> <span class="n">Ms</span><span class="p">.</span><span class="n">end</span><span class="p">();</span> <span class="n">I</span> <span class="o">!=</span> <span class="n">E</span><span class="p">;</span> <span class="o">++</span><span class="n">I</span><span class="p">)</span>
+      <span class="o">*</span><span class="n">I</span> <span class="o">=</span> <span class="n">Transform</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="o">*</span><span class="n">I</span><span class="p">));</span>
+
+    <span class="k">return</span> <span class="n">BaseLayer</span><span class="p">.</span><span class="n">addModuleSet</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Ms</span><span class="p">),</span> <span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">MemMgr</span><span class="p">),</span>
+                                <span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Resolver</span><span class="p">));</span>
+  <span class="p">}</span>
+
+  <span class="kt">void</span> <span class="n">removeModuleSet</span><span class="p">(</span><span class="n">ModuleSetHandleT</span> <span class="n">H</span><span class="p">)</span> <span class="p">{</span> <span class="n">BaseLayer</span><span class="p">.</span><span class="n">removeModuleSet</span><span class="p">(</span><span class="n">H</span><span class="p">);</span> <span class="p">}</span>
+
+  <span class="n">JITSymbol</span> <span class="n">findSymbol</span><span class="p">(</span><span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="o">&</span><span class="n">Name</span><span class="p">,</span> <span class="kt">bool</span> <span class="n">ExportedSymbolsOnly</span><span class="p">)</span> <span class="p">{</span>
+    <span class="k">return</span> <span class="n">BaseLayer</span><span class="p">.</span><span class="n">findSymbol</span><span class="p">(</span><span class="n">Name</span><span class="p">,</span> <span class="n">ExportedSymbolsOnly</span><span class="p">);</span>
+  <span class="p">}</span>
+
+  <span class="n">JITSymbol</span> <span class="n">findSymbolIn</span><span class="p">(</span><span class="n">ModuleSetHandleT</span> <span class="n">H</span><span class="p">,</span> <span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="o">&</span><span class="n">Name</span><span class="p">,</span>
+                         <span class="kt">bool</span> <span class="n">ExportedSymbolsOnly</span><span class="p">)</span> <span class="p">{</span>
+    <span class="k">return</span> <span class="n">BaseLayer</span><span class="p">.</span><span class="n">findSymbolIn</span><span class="p">(</span><span class="n">H</span><span class="p">,</span> <span class="n">Name</span><span class="p">,</span> <span class="n">ExportedSymbolsOnly</span><span class="p">);</span>
+  <span class="p">}</span>
+
+  <span class="kt">void</span> <span class="n">emitAndFinalize</span><span class="p">(</span><span class="n">ModuleSetHandleT</span> <span class="n">H</span><span class="p">)</span> <span class="p">{</span>
+    <span class="n">BaseLayer</span><span class="p">.</span><span class="n">emitAndFinalize</span><span class="p">(</span><span class="n">H</span><span class="p">);</span>
+  <span class="p">}</span>
+
+  <span class="n">TransformFtor</span><span class="o">&</span> <span class="n">getTransform</span><span class="p">()</span> <span class="p">{</span> <span class="k">return</span> <span class="n">Transform</span><span class="p">;</span> <span class="p">}</span>
+
+  <span class="k">const</span> <span class="n">TransformFtor</span><span class="o">&</span> <span class="n">getTransform</span><span class="p">()</span> <span class="k">const</span> <span class="p">{</span> <span class="k">return</span> <span class="n">Transform</span><span class="p">;</span> <span class="p">}</span>
+
+<span class="nl">private:</span>
+  <span class="n">BaseLayerT</span> <span class="o">&</span><span class="n">BaseLayer</span><span class="p">;</span>
+  <span class="n">TransformFtor</span> <span class="n">Transform</span><span class="p">;</span>
+<span class="p">};</span>
+</pre></div>
+</div>
+<p>This is the whole definition of IRTransformLayer, from
+<tt class="docutils literal"><span class="pre">llvm/include/llvm/ExecutionEngine/Orc/IRTransformLayer.h</span></tt>, stripped of its
+comments. It is a template class with two template arguments: <tt class="docutils literal"><span class="pre">BaesLayerT</span></tt> and
+<tt class="docutils literal"><span class="pre">TransformFtor</span></tt> that provide the type of the base layer and the type of the
+“transform functor” (in our case a std::function) respectively. This class is
+concerned with two very simple jobs: (1) Running every IR Module that is added
+with addModuleSet through the transform functor, and (2) conforming to the ORC
+layer interface. The interface consists of one typedef and five methods:</p>
+<table border="1" class="docutils">
+<colgroup>
+<col width="23%" />
+<col width="77%" />
+</colgroup>
+<thead valign="bottom">
+<tr class="row-odd"><th class="head">Interface</th>
+<th class="head">Description</th>
+</tr>
+</thead>
+<tbody valign="top">
+<tr class="row-even"><td>ModuleSetHandleT</td>
+<td>Provides a handle that can be used to identify a module
+set when calling findSymbolIn, removeModuleSet, or
+emitAndFinalize.</td>
+</tr>
+<tr class="row-odd"><td>addModuleSet</td>
+<td>Takes a given set of Modules and makes them “available
+for execution. This means that symbols in those modules
+should be searchable via findSymbol and findSymbolIn, and
+the address of the symbols should be read/writable (for
+data symbols), or executable (for function symbols) after
+JITSymbol::getAddress() is called. Note: This means that
+addModuleSet doesn’t have to compile (or do any other
+work) up-front. It <em>can</em>, like IRCompileLayer, act
+eagerly, but it can also simply record the module and
+take no further action until somebody calls
+JITSymbol::getAddress(). In IRTransformLayer’s case
+addModuleSet eagerly applies the transform functor to
+each module in the set, then passes the resulting set
+of mutated modules down to the layer below.</td>
+</tr>
+<tr class="row-even"><td>removeModuleSet</td>
+<td>Removes a set of modules from the JIT. Code or data
+defined in these modules will no longer be available, and
+the memory holding the JIT’d definitions will be freed.</td>
+</tr>
+<tr class="row-odd"><td>findSymbol</td>
+<td>Searches for the named symbol in all modules that have
+previously been added via addModuleSet (and not yet
+removed by a call to removeModuleSet). In
+IRTransformLayer we just pass the query on to the layer
+below. In our REPL this is our default way to search for
+function definitions.</td>
+</tr>
+<tr class="row-even"><td>findSymbolIn</td>
+<td>Searches for the named symbol in the module set indicated
+by the given ModuleSetHandleT. This is just an optimized
+search, better for lookup-speed when you know exactly
+a symbol definition should be found. In IRTransformLayer
+we just pass this query on to the layer below. In our
+REPL we use this method to search for functions
+representing top-level expressions, since we know exactly
+where we’ll find them: in the top-level expression module
+we just added.</td>
+</tr>
+<tr class="row-odd"><td>emitAndFinalize</td>
+<td>Forces all of the actions required to make the code and
+data in a module set (represented by a ModuleSetHandleT)
+accessible. Behaves as if some symbol in the set had been
+searched for and JITSymbol::getSymbolAddress called. This
+is rarely needed, but can be useful when dealing with
+layers that usually behave lazily if the user wants to
+trigger early compilation (for example, to use idle CPU
+time to eagerly compile code in the background).</td>
+</tr>
+</tbody>
+</table>
+<p>This interface attempts to capture the natural operations of a JIT (with some
+wrinkles like emitAndFinalize for performance), similar to the basic JIT API
+operations we identified in Chapter 1. Conforming to the layer concept allows
+classes to compose neatly by implementing their behaviors in terms of the these
+same operations, carried out on the layer below. For example, an eager layer
+(like IRTransformLayer) can implement addModuleSet by running each module in the
+set through its transform up-front and immediately passing the result to the
+layer below. A lazy layer, by contrast, could implement addModuleSet by
+squirreling away the modules doing no other up-front work, but applying the
+transform (and calling addModuleSet on the layer below) when the client calls
+findSymbol instead. The JIT’d program behavior will be the same either way, but
+these choices will have different performance characteristics: Doing work
+eagerly means the JIT takes longer up-front, but proceeds smoothly once this is
+done. Deferring work allows the JIT to get up-and-running quickly, but will
+force the JIT to pause and wait whenever some code or data is needed that hasn’t
+already been processed.</p>
+<p>Our current REPL is eager: Each function definition is optimized and compiled as
+soon as it’s typed in. If we were to make the transform layer lazy (but not
+change things otherwise) we could defer optimization until the first time we
+reference a function in a top-level expression (see if you can figure out why,
+then check out the answer below <a class="footnote-reference" href="#id3" id="id2">[1]</a>). In the next chapter, however we’ll
+introduce fully lazy compilation, in which function’s aren’t compiled until
+they’re first called at run-time. At this point the trade-offs get much more
+interesting: the lazier we are, the quicker we can start executing the first
+function, but the more often we’ll have to pause to compile newly encountered
+functions. If we only code-gen lazily, but optimize eagerly, we’ll have a slow
+startup (which everything is optimized) but relatively short pauses as each
+function just passes through code-gen. If we both optimize and code-gen lazily
+we can start executing the first function more quickly, but we’ll have longer
+pauses as each function has to be both optimized and code-gen’d when it’s first
+executed. Things become even more interesting if we consider interproceedural
+optimizations like inlining, which must be performed eagerly. These are
+complex trade-offs, and there is no one-size-fits all solution to them, but by
+providing composable layers we leave the decisions to the person implementing
+the JIT, and make it easy for them to experiment with different configurations.</p>
+<p><a class="reference external" href="BuildingAJIT3.html">Next: Adding Per-function Lazy Compilation</a></p>
+</div>
+<div class="section" id="full-code-listing">
+<h2><a class="toc-backref" href="#id6">2.3. Full Code Listing</a><a class="headerlink" href="#full-code-listing" title="Permalink to this headline">¶</a></h2>
+<p>Here is the complete code listing for our running example with an
+IRTransformLayer added to enable optimization. To build this example, use:</p>
+<div class="highlight-bash"><div class="highlight"><pre><span class="c"># Compile</span>
+clang++ -g toy.cpp <span class="sb">`</span>llvm-config --cxxflags --ldflags --system-libs --libs core orc native<span class="sb">`</span> -O3 -o toy
+<span class="c"># Run</span>
+./toy
+</pre></div>
+</div>
+<p>Here is the code:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">//===----- KaleidoscopeJIT.h - A simple JIT for Kaleidoscope ----*- C++ -*-===//</span>
+<span class="c1">//</span>
+<span class="c1">//                     The LLVM Compiler Infrastructure</span>
+<span class="c1">//</span>
+<span class="c1">// This file is distributed under the University of Illinois Open Source</span>
+<span class="c1">// License. See LICENSE.TXT for details.</span>
+<span class="c1">//</span>
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+<span class="c1">//</span>
+<span class="c1">// Contains a simple JIT definition for use in the kaleidoscope tutorials.</span>
+<span class="c1">//</span>
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+
+<span class="cp">#ifndef LLVM_EXECUTIONENGINE_ORC_KALEIDOSCOPEJIT_H</span>
+<span class="cp">#define LLVM_EXECUTIONENGINE_ORC_KALEIDOSCOPEJIT_H</span>
+
+<span class="cp">#include "llvm/ADT/STLExtras.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/ExecutionEngine.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/RuntimeDyld.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/SectionMemoryManager.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/CompileUtils.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/JITSymbol.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/IRCompileLayer.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/IRTransformLayer.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/LambdaResolver.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/ObjectLinkingLayer.h"</span>
+<span class="cp">#include "llvm/IR/DataLayout.h"</span>
+<span class="cp">#include "llvm/IR/Mangler.h"</span>
+<span class="cp">#include "llvm/Support/DynamicLibrary.h"</span>
+<span class="cp">#include "llvm/Support/raw_ostream.h"</span>
+<span class="cp">#include "llvm/Target/TargetMachine.h"</span>
+<span class="cp">#include <algorithm></span>
+<span class="cp">#include <memory></span>
+<span class="cp">#include <string></span>
+<span class="cp">#include <vector></span>
+
+<span class="k">namespace</span> <span class="n">llvm</span> <span class="p">{</span>
+<span class="k">namespace</span> <span class="n">orc</span> <span class="p">{</span>
+
+<span class="k">class</span> <span class="nc">KaleidoscopeJIT</span> <span class="p">{</span>
+<span class="nl">private:</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">TargetMachine</span><span class="o">></span> <span class="n">TM</span><span class="p">;</span>
+  <span class="k">const</span> <span class="n">DataLayout</span> <span class="n">DL</span><span class="p">;</span>
+  <span class="n">ObjectLinkingLayer</span><span class="o"><></span> <span class="n">ObjectLayer</span><span class="p">;</span>
+  <span class="n">IRCompileLayer</span><span class="o"><</span><span class="n">decltype</span><span class="p">(</span><span class="n">ObjectLayer</span><span class="p">)</span><span class="o">></span> <span class="n">CompileLayer</span><span class="p">;</span>
+
+  <span class="k">typedef</span> <span class="n">std</span><span class="o">::</span><span class="n">function</span><span class="o"><</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span><span class="p">)</span><span class="o">></span>
+    <span class="n">OptimizeFunction</span><span class="p">;</span>
+
+  <span class="n">IRTransformLayer</span><span class="o"><</span><span class="n">decltype</span><span class="p">(</span><span class="n">CompileLayer</span><span class="p">),</span> <span class="n">OptimizeFunction</span><span class="o">></span> <span class="n">OptimizeLayer</span><span class="p">;</span>
+
+<span class="nl">public:</span>
+  <span class="k">typedef</span> <span class="n">decltype</span><span class="p">(</span><span class="n">OptimizeLayer</span><span class="p">)</span><span class="o">::</span><span class="n">ModuleSetHandleT</span> <span class="n">ModuleHandle</span><span class="p">;</span>
+
+  <span class="n">KaleidoscopeJIT</span><span class="p">()</span>
+      <span class="o">:</span> <span class="n">TM</span><span class="p">(</span><span class="n">EngineBuilder</span><span class="p">().</span><span class="n">selectTarget</span><span class="p">()),</span> <span class="n">DL</span><span class="p">(</span><span class="n">TM</span><span class="o">-></span><span class="n">createDataLayout</span><span class="p">()),</span>
+        <span class="n">CompileLayer</span><span class="p">(</span><span class="n">ObjectLayer</span><span class="p">,</span> <span class="n">SimpleCompiler</span><span class="p">(</span><span class="o">*</span><span class="n">TM</span><span class="p">)),</span>
+        <span class="n">OptimizeLayer</span><span class="p">(</span><span class="n">CompileLayer</span><span class="p">,</span>
+                      <span class="p">[</span><span class="k">this</span><span class="p">](</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span> <span class="n">M</span><span class="p">)</span> <span class="p">{</span>
+                        <span class="k">return</span> <span class="n">optimizeModule</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">M</span><span class="p">));</span>
+                      <span class="p">})</span> <span class="p">{</span>
+    <span class="n">llvm</span><span class="o">::</span><span class="n">sys</span><span class="o">::</span><span class="n">DynamicLibrary</span><span class="o">::</span><span class="n">LoadLibraryPermanently</span><span class="p">(</span><span class="n">nullptr</span><span class="p">);</span>
+  <span class="p">}</span>
+
+  <span class="n">TargetMachine</span> <span class="o">&</span><span class="n">getTargetMachine</span><span class="p">()</span> <span class="p">{</span> <span class="k">return</span> <span class="o">*</span><span class="n">TM</span><span class="p">;</span> <span class="p">}</span>
+
+  <span class="n">ModuleHandle</span> <span class="n">addModule</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span> <span class="n">M</span><span class="p">)</span> <span class="p">{</span>
+    <span class="c1">// Build our symbol resolver:</span>
+    <span class="c1">// Lambda 1: Look back into the JIT itself to find symbols that are part of</span>
+    <span class="c1">//           the same "logical dylib".</span>
+    <span class="c1">// Lambda 2: Search for external symbols in the host process.</span>
+    <span class="k">auto</span> <span class="n">Resolver</span> <span class="o">=</span> <span class="n">createLambdaResolver</span><span class="p">(</span>
+        <span class="p">[</span><span class="o">&</span><span class="p">](</span><span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="o">&</span><span class="n">Name</span><span class="p">)</span> <span class="p">{</span>
+          <span class="k">if</span> <span class="p">(</span><span class="k">auto</span> <span class="n">Sym</span> <span class="o">=</span> <span class="n">OptimizeLayer</span><span class="p">.</span><span class="n">findSymbol</span><span class="p">(</span><span class="n">Name</span><span class="p">,</span> <span class="nb">false</span><span class="p">))</span>
+            <span class="k">return</span> <span class="n">Sym</span><span class="p">.</span><span class="n">toRuntimeDyldSymbol</span><span class="p">();</span>
+          <span class="k">return</span> <span class="n">RuntimeDyld</span><span class="o">::</span><span class="n">SymbolInfo</span><span class="p">(</span><span class="n">nullptr</span><span class="p">);</span>
+        <span class="p">},</span>
+        <span class="p">[](</span><span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="o">&</span><span class="n">Name</span><span class="p">)</span> <span class="p">{</span>
+          <span class="k">if</span> <span class="p">(</span><span class="k">auto</span> <span class="n">SymAddr</span> <span class="o">=</span>
+                <span class="n">RTDyldMemoryManager</span><span class="o">::</span><span class="n">getSymbolAddressInProcess</span><span class="p">(</span><span class="n">Name</span><span class="p">))</span>
+            <span class="k">return</span> <span class="n">RuntimeDyld</span><span class="o">::</span><span class="n">SymbolInfo</span><span class="p">(</span><span class="n">SymAddr</span><span class="p">,</span> <span class="n">JITSymbolFlags</span><span class="o">::</span><span class="n">Exported</span><span class="p">);</span>
+          <span class="k">return</span> <span class="n">RuntimeDyld</span><span class="o">::</span><span class="n">SymbolInfo</span><span class="p">(</span><span class="n">nullptr</span><span class="p">);</span>
+        <span class="p">});</span>
+
+    <span class="c1">// Build a singlton module set to hold our module.</span>
+    <span class="n">std</span><span class="o">::</span><span class="n">vector</span><span class="o"><</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">>></span> <span class="n">Ms</span><span class="p">;</span>
+    <span class="n">Ms</span><span class="p">.</span><span class="n">push_back</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">M</span><span class="p">));</span>
+
+    <span class="c1">// Add the set to the JIT with the resolver we created above and a newly</span>
+    <span class="c1">// created SectionMemoryManager.</span>
+    <span class="k">return</span> <span class="n">OptimizeLayer</span><span class="p">.</span><span class="n">addModuleSet</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Ms</span><span class="p">),</span>
+                                      <span class="n">make_unique</span><span class="o"><</span><span class="n">SectionMemoryManager</span><span class="o">></span><span class="p">(),</span>
+                                      <span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Resolver</span><span class="p">));</span>
+  <span class="p">}</span>
+
+  <span class="n">JITSymbol</span> <span class="n">findSymbol</span><span class="p">(</span><span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="n">Name</span><span class="p">)</span> <span class="p">{</span>
+    <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="n">MangledName</span><span class="p">;</span>
+    <span class="n">raw_string_ostream</span> <span class="nf">MangledNameStream</span><span class="p">(</span><span class="n">MangledName</span><span class="p">);</span>
+    <span class="n">Mangler</span><span class="o">::</span><span class="n">getNameWithPrefix</span><span class="p">(</span><span class="n">MangledNameStream</span><span class="p">,</span> <span class="n">Name</span><span class="p">,</span> <span class="n">DL</span><span class="p">);</span>
+    <span class="k">return</span> <span class="n">OptimizeLayer</span><span class="p">.</span><span class="n">findSymbol</span><span class="p">(</span><span class="n">MangledNameStream</span><span class="p">.</span><span class="n">str</span><span class="p">(),</span> <span class="nb">true</span><span class="p">);</span>
+  <span class="p">}</span>
+
+  <span class="kt">void</span> <span class="n">removeModule</span><span class="p">(</span><span class="n">ModuleHandle</span> <span class="n">H</span><span class="p">)</span> <span class="p">{</span>
+    <span class="n">OptimizeLayer</span><span class="p">.</span><span class="n">removeModuleSet</span><span class="p">(</span><span class="n">H</span><span class="p">);</span>
+  <span class="p">}</span>
+
+<span class="nl">private:</span>
+
+  <span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span> <span class="n">optimizeModule</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span> <span class="n">M</span><span class="p">)</span> <span class="p">{</span>
+    <span class="c1">// Create a function pass manager.</span>
+    <span class="k">auto</span> <span class="n">FPM</span> <span class="o">=</span> <span class="n">llvm</span><span class="o">::</span><span class="n">make_unique</span><span class="o"><</span><span class="n">legacy</span><span class="o">::</span><span class="n">FunctionPassManager</span><span class="o">></span><span class="p">(</span><span class="n">M</span><span class="p">.</span><span class="n">get</span><span class="p">());</span>
+
+    <span class="c1">// Add some optimizations.</span>
+    <span class="n">FPM</span><span class="o">-></span><span class="n">add</span><span class="p">(</span><span class="n">createInstructionCombiningPass</span><span class="p">());</span>
+    <span class="n">FPM</span><span class="o">-></span><span class="n">add</span><span class="p">(</span><span class="n">createReassociatePass</span><span class="p">());</span>
+    <span class="n">FPM</span><span class="o">-></span><span class="n">add</span><span class="p">(</span><span class="n">createGVNPass</span><span class="p">());</span>
+    <span class="n">FPM</span><span class="o">-></span><span class="n">add</span><span class="p">(</span><span class="n">createCFGSimplificationPass</span><span class="p">());</span>
+    <span class="n">FPM</span><span class="o">-></span><span class="n">doInitialization</span><span class="p">();</span>
+
+    <span class="c1">// Run the optimizations over all functions in the module being added to</span>
+    <span class="c1">// the JIT.</span>
+    <span class="k">for</span> <span class="p">(</span><span class="k">auto</span> <span class="o">&</span><span class="n">F</span> <span class="o">:</span> <span class="o">*</span><span class="n">M</span><span class="p">)</span>
+      <span class="n">FPM</span><span class="o">-></span><span class="n">run</span><span class="p">(</span><span class="n">F</span><span class="p">);</span>
+
+    <span class="k">return</span> <span class="n">M</span><span class="p">;</span>
+  <span class="p">}</span>
+
+<span class="p">};</span>
+
+<span class="p">}</span> <span class="c1">// end namespace orc</span>
+<span class="p">}</span> <span class="c1">// end namespace llvm</span>
+
+<span class="cp">#endif </span><span class="c1">// LLVM_EXECUTIONENGINE_ORC_KALEIDOSCOPEJIT_H</span>
+</pre></div>
+</div>
+<table class="docutils footnote" frame="void" id="id3" rules="none">
+<colgroup><col class="label" /><col /></colgroup>
+<tbody valign="top">
+<tr><td class="label"><a class="fn-backref" href="#id2">[1]</a></td><td>When we add our top-level expression to the JIT, any calls to functions
+that we defined earlier will appear to the ObjectLinkingLayer as
+external symbols. The ObjectLinkingLayer will call the SymbolResolver
+that we defined in addModuleSet, which in turn calls findSymbol on the
+OptimizeLayer, at which point even a lazy transform layer will have to
+do its work.</td></tr>
+</tbody>
+</table>
+</div>
+</div>
+
+
+          </div>
+      </div>
+      <div class="clearer"></div>
+    </div>
+    <div class="related">
+      <h3>Navigation</h3>
+      <ul>
+        <li class="right" style="margin-right: 10px">
+          <a href="../genindex.html" title="General Index"
+             >index</a></li>
+        <li class="right" >
+          <a href="BuildingAJIT3.html" title="3. Building a JIT: Per-function Lazy Compilation"
+             >next</a> |</li>
+        <li class="right" >
+          <a href="BuildingAJIT1.html" title="1. Building a JIT: Starting out with KaleidoscopeJIT"
+             >previous</a> |</li>
+  <li><a href="http://llvm.org/">LLVM Home</a> | </li>
+  <li><a href="../index.html">Documentation</a>»</li>
+
+          <li><a href="index.html" >LLVM Tutorial: Table of Contents</a> »</li> 
+      </ul>
+    </div>
+    <div class="footer">
+        © Copyright 2003-2016, LLVM Project.
+      Last updated on 2016-12-21.
+      Created using <a href="http://sphinx-doc.org/">Sphinx</a> 1.2.2.
+    </div>
+  </body>
+</html>
\ No newline at end of file

Added: www-releases/trunk/3.9.1/docs/tutorial/BuildingAJIT3.html
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/tutorial/BuildingAJIT3.html?rev=290368&view=auto
==============================================================================
--- www-releases/trunk/3.9.1/docs/tutorial/BuildingAJIT3.html (added)
+++ www-releases/trunk/3.9.1/docs/tutorial/BuildingAJIT3.html Thu Dec 22 14:04:03 2016
@@ -0,0 +1,399 @@
+
+<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN"
+  "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd">
+
+
+<html xmlns="http://www.w3.org/1999/xhtml">
+  <head>
+    <meta http-equiv="Content-Type" content="text/html; charset=utf-8" />
+    
+    <title>3. Building a JIT: Per-function Lazy Compilation — LLVM 3.9 documentation</title>
+    
+    <link rel="stylesheet" href="../_static/llvm-theme.css" type="text/css" />
+    <link rel="stylesheet" href="../_static/pygments.css" type="text/css" />
+    
+    <script type="text/javascript">
+      var DOCUMENTATION_OPTIONS = {
+        URL_ROOT:    '../',
+        VERSION:     '3.9',
+        COLLAPSE_INDEX: false,
+        FILE_SUFFIX: '.html',
+        HAS_SOURCE:  true
+      };
+    </script>
+    <script type="text/javascript" src="../_static/jquery.js"></script>
+    <script type="text/javascript" src="../_static/underscore.js"></script>
+    <script type="text/javascript" src="../_static/doctools.js"></script>
+    <link rel="top" title="LLVM 3.9 documentation" href="../index.html" />
+    <link rel="up" title="LLVM Tutorial: Table of Contents" href="index.html" />
+    <link rel="next" title="4. Building a JIT: Extreme Laziness - Using Compile Callbacks to JIT from ASTs" href="BuildingAJIT4.html" />
+    <link rel="prev" title="2. Building a JIT: Adding Optimizations – An introduction to ORC Layers" href="BuildingAJIT2.html" />
+<style type="text/css">
+  table.right { float: right; margin-left: 20px; }
+  table.right td { border: 1px solid #ccc; }
+</style>
+
+  </head>
+  <body>
+<div class="logo">
+  <a href="../index.html">
+    <img src="../_static/logo.png"
+         alt="LLVM Logo" width="250" height="88"/></a>
+</div>
+
+    <div class="related">
+      <h3>Navigation</h3>
+      <ul>
+        <li class="right" style="margin-right: 10px">
+          <a href="../genindex.html" title="General Index"
+             accesskey="I">index</a></li>
+        <li class="right" >
+          <a href="BuildingAJIT4.html" title="4. Building a JIT: Extreme Laziness - Using Compile Callbacks to JIT from ASTs"
+             accesskey="N">next</a> |</li>
+        <li class="right" >
+          <a href="BuildingAJIT2.html" title="2. Building a JIT: Adding Optimizations – An introduction to ORC Layers"
+             accesskey="P">previous</a> |</li>
+  <li><a href="http://llvm.org/">LLVM Home</a> | </li>
+  <li><a href="../index.html">Documentation</a>»</li>
+
+          <li><a href="index.html" accesskey="U">LLVM Tutorial: Table of Contents</a> »</li> 
+      </ul>
+    </div>
+
+
+    <div class="document">
+      <div class="documentwrapper">
+          <div class="body">
+            
+  <div class="section" id="building-a-jit-per-function-lazy-compilation">
+<h1>3. Building a JIT: Per-function Lazy Compilation<a class="headerlink" href="#building-a-jit-per-function-lazy-compilation" title="Permalink to this headline">¶</a></h1>
+<div class="contents local topic" id="contents">
+<ul class="simple">
+<li><a class="reference internal" href="#chapter-3-introduction" id="id1">Chapter 3 Introduction</a></li>
+<li><a class="reference internal" href="#lazy-compilation" id="id2">Lazy Compilation</a></li>
+<li><a class="reference internal" href="#full-code-listing" id="id3">Full Code Listing</a></li>
+</ul>
+</div>
+<p><strong>This tutorial is under active development. It is incomplete and details may
+change frequently.</strong> Nonetheless we invite you to try it out as it stands, and
+we welcome any feedback.</p>
+<div class="section" id="chapter-3-introduction">
+<h2><a class="toc-backref" href="#id1">3.1. Chapter 3 Introduction</a><a class="headerlink" href="#chapter-3-introduction" title="Permalink to this headline">¶</a></h2>
+<p>Welcome to Chapter 3 of the “Building an ORC-based JIT in LLVM” tutorial. This
+chapter discusses lazy JITing and shows you how to enable it by adding an ORC
+CompileOnDemand layer the JIT from <a class="reference external" href="BuildingAJIT2.html">Chapter 2</a>.</p>
+</div>
+<div class="section" id="lazy-compilation">
+<h2><a class="toc-backref" href="#id2">3.2. Lazy Compilation</a><a class="headerlink" href="#lazy-compilation" title="Permalink to this headline">¶</a></h2>
+<p>When we add a module to the KaleidoscopeJIT class described in Chapter 2 it is
+immediately optimized, compiled and linked for us by the IRTransformLayer,
+IRCompileLayer and ObjectLinkingLayer respectively. This scheme, where all the
+work to make a Module executable is done up front, is relatively simple to
+understand its performance characteristics are easy to reason about. However,
+it will lead to very high startup times if the amount of code to be compiled is
+large, and may also do a lot of unnecessary compilation if only a few compiled
+functions are ever called at runtime. A truly “just-in-time” compiler should
+allow us to defer the compilation of any given function until the moment that
+function is first called, improving launch times and eliminating redundant work.
+In fact, the ORC APIs provide us with a layer to lazily compile LLVM IR:
+<em>CompileOnDemandLayer</em>.</p>
+<p>The CompileOnDemandLayer conforms to the layer interface described in Chapter 2,
+but the addModuleSet method behaves quite differently from the layers we have
+seen so far: rather than doing any work up front, it just constructs a <em>stub</em>
+for each function in the module and arranges for the stub to trigger compilation
+of the actual function the first time it is called. Because stub functions are
+very cheap to produce CompileOnDemand’s addModuleSet method runs very quickly,
+reducing the time required to launch the first function to be executed, and
+saving us from doing any redundant compilation. By conforming to the layer
+interface, CompileOnDemand can be easily added on top of our existing JIT class.
+We just need a few changes:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="p">...</span>
+<span class="cp">#include "llvm/ExecutionEngine/SectionMemoryManager.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/CompileOnDemandLayer.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/CompileUtils.h"</span>
+<span class="p">...</span>
+
+<span class="p">...</span>
+<span class="k">class</span> <span class="nc">KaleidoscopeJIT</span> <span class="p">{</span>
+<span class="nl">private:</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">TargetMachine</span><span class="o">></span> <span class="n">TM</span><span class="p">;</span>
+  <span class="k">const</span> <span class="n">DataLayout</span> <span class="n">DL</span><span class="p">;</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">JITCompileCallbackManager</span><span class="o">></span> <span class="n">CompileCallbackManager</span><span class="p">;</span>
+  <span class="n">ObjectLinkingLayer</span><span class="o"><></span> <span class="n">ObjectLayer</span><span class="p">;</span>
+  <span class="n">IRCompileLayer</span><span class="o"><</span><span class="n">decltype</span><span class="p">(</span><span class="n">ObjectLayer</span><span class="p">)</span><span class="o">></span> <span class="n">CompileLayer</span><span class="p">;</span>
+
+  <span class="k">typedef</span> <span class="n">std</span><span class="o">::</span><span class="n">function</span><span class="o"><</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span><span class="p">)</span><span class="o">></span>
+    <span class="n">OptimizeFunction</span><span class="p">;</span>
+
+  <span class="n">IRTransformLayer</span><span class="o"><</span><span class="n">decltype</span><span class="p">(</span><span class="n">CompileLayer</span><span class="p">),</span> <span class="n">OptimizeFunction</span><span class="o">></span> <span class="n">OptimizeLayer</span><span class="p">;</span>
+  <span class="n">CompileOnDemandLayer</span><span class="o"><</span><span class="n">decltype</span><span class="p">(</span><span class="n">OptimizeLayer</span><span class="p">)</span><span class="o">></span> <span class="n">CODLayer</span><span class="p">;</span>
+
+<span class="nl">public:</span>
+  <span class="k">typedef</span> <span class="n">decltype</span><span class="p">(</span><span class="n">CODLayer</span><span class="p">)</span><span class="o">::</span><span class="n">ModuleSetHandleT</span> <span class="n">ModuleHandle</span><span class="p">;</span>
+</pre></div>
+</div>
+<p>First we need to include the CompileOnDemandLayer.h header, then add two new
+members: a std::unique_ptr<CompileCallbackManager> and a CompileOnDemandLayer,
+to our class. The CompileCallbackManager is a utility that enables us to
+create re-entry points into the compiler for functions that we want to lazily
+compile. In the next chapter we’ll be looking at this class in detail, but for
+now we’ll be treating it as an opaque utility: We just need to pass a reference
+to it into our new CompileOnDemandLayer, and the layer will do all the work of
+setting up the callbacks using the callback manager we gave it.</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="n">KaleidoscopeJIT</span><span class="p">()</span>
+    <span class="o">:</span> <span class="n">TM</span><span class="p">(</span><span class="n">EngineBuilder</span><span class="p">().</span><span class="n">selectTarget</span><span class="p">()),</span> <span class="n">DL</span><span class="p">(</span><span class="n">TM</span><span class="o">-></span><span class="n">createDataLayout</span><span class="p">()),</span>
+      <span class="n">CompileLayer</span><span class="p">(</span><span class="n">ObjectLayer</span><span class="p">,</span> <span class="n">SimpleCompiler</span><span class="p">(</span><span class="o">*</span><span class="n">TM</span><span class="p">)),</span>
+      <span class="n">OptimizeLayer</span><span class="p">(</span><span class="n">CompileLayer</span><span class="p">,</span>
+                    <span class="p">[</span><span class="k">this</span><span class="p">](</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span> <span class="n">M</span><span class="p">)</span> <span class="p">{</span>
+                      <span class="k">return</span> <span class="n">optimizeModule</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">M</span><span class="p">));</span>
+                    <span class="p">}),</span>
+      <span class="n">CompileCallbackManager</span><span class="p">(</span>
+          <span class="n">orc</span><span class="o">::</span><span class="n">createLocalCompileCallbackManager</span><span class="p">(</span><span class="n">TM</span><span class="o">-></span><span class="n">getTargetTriple</span><span class="p">(),</span> <span class="mi">0</span><span class="p">)),</span>
+      <span class="n">CODLayer</span><span class="p">(</span><span class="n">OptimizeLayer</span><span class="p">,</span>
+               <span class="p">[</span><span class="k">this</span><span class="p">](</span><span class="n">Function</span> <span class="o">&</span><span class="n">F</span><span class="p">)</span> <span class="p">{</span> <span class="k">return</span> <span class="n">std</span><span class="o">::</span><span class="n">set</span><span class="o"><</span><span class="n">Function</span><span class="o">*></span><span class="p">({</span><span class="o">&</span><span class="n">F</span><span class="p">});</span> <span class="p">},</span>
+               <span class="o">*</span><span class="n">CompileCallbackManager</span><span class="p">,</span>
+               <span class="n">orc</span><span class="o">::</span><span class="n">createLocalIndirectStubsManagerBuilder</span><span class="p">(</span>
+                 <span class="n">TM</span><span class="o">-></span><span class="n">getTargetTriple</span><span class="p">()))</span> <span class="p">{</span>
+  <span class="n">llvm</span><span class="o">::</span><span class="n">sys</span><span class="o">::</span><span class="n">DynamicLibrary</span><span class="o">::</span><span class="n">LoadLibraryPermanently</span><span class="p">(</span><span class="n">nullptr</span><span class="p">);</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>Next we have to update our constructor to initialize the new members. To create
+an appropriate compile callback manager we use the
+createLocalCompileCallbackManager function, which takes a TargetMachine and a
+TargetAddress to call if it receives a request to compile an unknown function.
+In our simple JIT this situation is unlikely to come up, so we’ll cheat and
+just pass ‘0’ here. In a production quality JIT you could give the address of a
+function that throws an exception in order to unwind the JIT’d code stack.</p>
+<p>Now we can construct our CompileOnDemandLayer. Following the pattern from
+previous layers we start by passing a reference to the next layer down in our
+stack – the OptimizeLayer. Next we need to supply a ‘partitioning function’:
+when a not-yet-compiled function is called, the CompileOnDemandLayer will call
+this function to ask us what we would like to compile. At a minimum we need to
+compile the function being called (given by the argument to the partitioning
+function), but we could also request that the CompileOnDemandLayer compile other
+functions that are unconditionally called (or highly likely to be called) from
+the function being called. For KaleidoscopeJIT we’ll keep it simple and just
+request compilation of the function that was called. Next we pass a reference to
+our CompileCallbackManager. Finally, we need to supply an “indirect stubs
+manager builder”. This is a function that constructs IndirectStubManagers, which
+are in turn used to build the stubs for each module. The CompileOnDemandLayer
+will call the indirect stub manager builder once for each call to addModuleSet,
+and use the resulting indirect stubs manager to create stubs for all functions
+in all modules added. If/when the module set is removed from the JIT the
+indirect stubs manager will be deleted, freeing any memory allocated to the
+stubs. We supply this function by using the
+createLocalIndirectStubsManagerBuilder utility.</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">// ...</span>
+        <span class="k">if</span> <span class="p">(</span><span class="k">auto</span> <span class="n">Sym</span> <span class="o">=</span> <span class="n">CODLayer</span><span class="p">.</span><span class="n">findSymbol</span><span class="p">(</span><span class="n">Name</span><span class="p">,</span> <span class="nb">false</span><span class="p">))</span>
+<span class="c1">// ...</span>
+<span class="k">return</span> <span class="n">CODLayer</span><span class="p">.</span><span class="n">addModuleSet</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Ms</span><span class="p">),</span>
+                             <span class="n">make_unique</span><span class="o"><</span><span class="n">SectionMemoryManager</span><span class="o">></span><span class="p">(),</span>
+                             <span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Resolver</span><span class="p">));</span>
+<span class="c1">// ...</span>
+
+<span class="c1">// ...</span>
+<span class="k">return</span> <span class="n">CODLayer</span><span class="p">.</span><span class="n">findSymbol</span><span class="p">(</span><span class="n">MangledNameStream</span><span class="p">.</span><span class="n">str</span><span class="p">(),</span> <span class="nb">true</span><span class="p">);</span>
+<span class="c1">// ...</span>
+
+<span class="c1">// ...</span>
+<span class="n">CODLayer</span><span class="p">.</span><span class="n">removeModuleSet</span><span class="p">(</span><span class="n">H</span><span class="p">);</span>
+<span class="c1">// ...</span>
+</pre></div>
+</div>
+<p>Finally, we need to replace the references to OptimizeLayer in our addModule,
+findSymbol, and removeModule methods. With that, we’re up and running.</p>
+<p><strong>To be done:</strong></p>
+<p>** Discuss CompileCallbackManagers and IndirectStubManagers in more detail.**</p>
+</div>
+<div class="section" id="full-code-listing">
+<h2><a class="toc-backref" href="#id3">3.3. Full Code Listing</a><a class="headerlink" href="#full-code-listing" title="Permalink to this headline">¶</a></h2>
+<p>Here is the complete code listing for our running example with a CompileOnDemand
+layer added to enable lazy function-at-a-time compilation. To build this example, use:</p>
+<div class="highlight-bash"><div class="highlight"><pre><span class="c"># Compile</span>
+clang++ -g toy.cpp <span class="sb">`</span>llvm-config --cxxflags --ldflags --system-libs --libs core orc native<span class="sb">`</span> -O3 -o toy
+<span class="c"># Run</span>
+./toy
+</pre></div>
+</div>
+<p>Here is the code:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">//===----- KaleidoscopeJIT.h - A simple JIT for Kaleidoscope ----*- C++ -*-===//</span>
+<span class="c1">//</span>
+<span class="c1">//                     The LLVM Compiler Infrastructure</span>
+<span class="c1">//</span>
+<span class="c1">// This file is distributed under the University of Illinois Open Source</span>
+<span class="c1">// License. See LICENSE.TXT for details.</span>
+<span class="c1">//</span>
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+<span class="c1">//</span>
+<span class="c1">// Contains a simple JIT definition for use in the kaleidoscope tutorials.</span>
+<span class="c1">//</span>
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+
+<span class="cp">#ifndef LLVM_EXECUTIONENGINE_ORC_KALEIDOSCOPEJIT_H</span>
+<span class="cp">#define LLVM_EXECUTIONENGINE_ORC_KALEIDOSCOPEJIT_H</span>
+
+<span class="cp">#include "llvm/ADT/STLExtras.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/ExecutionEngine.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/RuntimeDyld.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/SectionMemoryManager.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/CompileOnDemandLayer.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/CompileUtils.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/JITSymbol.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/IRCompileLayer.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/IRTransformLayer.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/LambdaResolver.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/ObjectLinkingLayer.h"</span>
+<span class="cp">#include "llvm/IR/DataLayout.h"</span>
+<span class="cp">#include "llvm/IR/Mangler.h"</span>
+<span class="cp">#include "llvm/Support/DynamicLibrary.h"</span>
+<span class="cp">#include "llvm/Support/raw_ostream.h"</span>
+<span class="cp">#include "llvm/Target/TargetMachine.h"</span>
+<span class="cp">#include <algorithm></span>
+<span class="cp">#include <memory></span>
+<span class="cp">#include <string></span>
+<span class="cp">#include <vector></span>
+
+<span class="k">namespace</span> <span class="n">llvm</span> <span class="p">{</span>
+<span class="k">namespace</span> <span class="n">orc</span> <span class="p">{</span>
+
+<span class="k">class</span> <span class="nc">KaleidoscopeJIT</span> <span class="p">{</span>
+<span class="nl">private:</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">TargetMachine</span><span class="o">></span> <span class="n">TM</span><span class="p">;</span>
+  <span class="k">const</span> <span class="n">DataLayout</span> <span class="n">DL</span><span class="p">;</span>
+  <span class="n">ObjectLinkingLayer</span><span class="o"><></span> <span class="n">ObjectLayer</span><span class="p">;</span>
+  <span class="n">IRCompileLayer</span><span class="o"><</span><span class="n">decltype</span><span class="p">(</span><span class="n">ObjectLayer</span><span class="p">)</span><span class="o">></span> <span class="n">CompileLayer</span><span class="p">;</span>
+
+  <span class="k">typedef</span> <span class="n">std</span><span class="o">::</span><span class="n">function</span><span class="o"><</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span><span class="p">)</span><span class="o">></span>
+    <span class="n">OptimizeFunction</span><span class="p">;</span>
+
+  <span class="n">IRTransformLayer</span><span class="o"><</span><span class="n">decltype</span><span class="p">(</span><span class="n">CompileLayer</span><span class="p">),</span> <span class="n">OptimizeFunction</span><span class="o">></span> <span class="n">OptimizeLayer</span><span class="p">;</span>
+
+  <span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">JITCompileCallbackManager</span><span class="o">></span> <span class="n">CompileCallbackManager</span><span class="p">;</span>
+  <span class="n">CompileOnDemandLayer</span><span class="o"><</span><span class="n">decltype</span><span class="p">(</span><span class="n">OptimizeLayer</span><span class="p">)</span><span class="o">></span> <span class="n">CODLayer</span><span class="p">;</span>
+
+<span class="nl">public:</span>
+  <span class="k">typedef</span> <span class="n">decltype</span><span class="p">(</span><span class="n">CODLayer</span><span class="p">)</span><span class="o">::</span><span class="n">ModuleSetHandleT</span> <span class="n">ModuleHandle</span><span class="p">;</span>
+
+  <span class="n">KaleidoscopeJIT</span><span class="p">()</span>
+      <span class="o">:</span> <span class="n">TM</span><span class="p">(</span><span class="n">EngineBuilder</span><span class="p">().</span><span class="n">selectTarget</span><span class="p">()),</span> <span class="n">DL</span><span class="p">(</span><span class="n">TM</span><span class="o">-></span><span class="n">createDataLayout</span><span class="p">()),</span>
+        <span class="n">CompileLayer</span><span class="p">(</span><span class="n">ObjectLayer</span><span class="p">,</span> <span class="n">SimpleCompiler</span><span class="p">(</span><span class="o">*</span><span class="n">TM</span><span class="p">)),</span>
+        <span class="n">OptimizeLayer</span><span class="p">(</span><span class="n">CompileLayer</span><span class="p">,</span>
+                      <span class="p">[</span><span class="k">this</span><span class="p">](</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span> <span class="n">M</span><span class="p">)</span> <span class="p">{</span>
+                        <span class="k">return</span> <span class="n">optimizeModule</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">M</span><span class="p">));</span>
+                      <span class="p">}),</span>
+        <span class="n">CompileCallbackManager</span><span class="p">(</span>
+            <span class="n">orc</span><span class="o">::</span><span class="n">createLocalCompileCallbackManager</span><span class="p">(</span><span class="n">TM</span><span class="o">-></span><span class="n">getTargetTriple</span><span class="p">(),</span> <span class="mi">0</span><span class="p">)),</span>
+        <span class="n">CODLayer</span><span class="p">(</span><span class="n">OptimizeLayer</span><span class="p">,</span>
+                 <span class="p">[</span><span class="k">this</span><span class="p">](</span><span class="n">Function</span> <span class="o">&</span><span class="n">F</span><span class="p">)</span> <span class="p">{</span> <span class="k">return</span> <span class="n">std</span><span class="o">::</span><span class="n">set</span><span class="o"><</span><span class="n">Function</span><span class="o">*></span><span class="p">({</span><span class="o">&</span><span class="n">F</span><span class="p">});</span> <span class="p">},</span>
+                 <span class="o">*</span><span class="n">CompileCallbackManager</span><span class="p">,</span>
+                 <span class="n">orc</span><span class="o">::</span><span class="n">createLocalIndirectStubsManagerBuilder</span><span class="p">(</span>
+                   <span class="n">TM</span><span class="o">-></span><span class="n">getTargetTriple</span><span class="p">()))</span> <span class="p">{</span>
+    <span class="n">llvm</span><span class="o">::</span><span class="n">sys</span><span class="o">::</span><span class="n">DynamicLibrary</span><span class="o">::</span><span class="n">LoadLibraryPermanently</span><span class="p">(</span><span class="n">nullptr</span><span class="p">);</span>
+  <span class="p">}</span>
+
+  <span class="n">TargetMachine</span> <span class="o">&</span><span class="n">getTargetMachine</span><span class="p">()</span> <span class="p">{</span> <span class="k">return</span> <span class="o">*</span><span class="n">TM</span><span class="p">;</span> <span class="p">}</span>
+
+  <span class="n">ModuleHandle</span> <span class="n">addModule</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span> <span class="n">M</span><span class="p">)</span> <span class="p">{</span>
+    <span class="c1">// Build our symbol resolver:</span>
+    <span class="c1">// Lambda 1: Look back into the JIT itself to find symbols that are part of</span>
+    <span class="c1">//           the same "logical dylib".</span>
+    <span class="c1">// Lambda 2: Search for external symbols in the host process.</span>
+    <span class="k">auto</span> <span class="n">Resolver</span> <span class="o">=</span> <span class="n">createLambdaResolver</span><span class="p">(</span>
+        <span class="p">[</span><span class="o">&</span><span class="p">](</span><span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="o">&</span><span class="n">Name</span><span class="p">)</span> <span class="p">{</span>
+          <span class="k">if</span> <span class="p">(</span><span class="k">auto</span> <span class="n">Sym</span> <span class="o">=</span> <span class="n">CODLayer</span><span class="p">.</span><span class="n">findSymbol</span><span class="p">(</span><span class="n">Name</span><span class="p">,</span> <span class="nb">false</span><span class="p">))</span>
+            <span class="k">return</span> <span class="n">Sym</span><span class="p">.</span><span class="n">toRuntimeDyldSymbol</span><span class="p">();</span>
+          <span class="k">return</span> <span class="n">RuntimeDyld</span><span class="o">::</span><span class="n">SymbolInfo</span><span class="p">(</span><span class="n">nullptr</span><span class="p">);</span>
+        <span class="p">},</span>
+        <span class="p">[](</span><span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="o">&</span><span class="n">Name</span><span class="p">)</span> <span class="p">{</span>
+          <span class="k">if</span> <span class="p">(</span><span class="k">auto</span> <span class="n">SymAddr</span> <span class="o">=</span>
+                <span class="n">RTDyldMemoryManager</span><span class="o">::</span><span class="n">getSymbolAddressInProcess</span><span class="p">(</span><span class="n">Name</span><span class="p">))</span>
+            <span class="k">return</span> <span class="n">RuntimeDyld</span><span class="o">::</span><span class="n">SymbolInfo</span><span class="p">(</span><span class="n">SymAddr</span><span class="p">,</span> <span class="n">JITSymbolFlags</span><span class="o">::</span><span class="n">Exported</span><span class="p">);</span>
+          <span class="k">return</span> <span class="n">RuntimeDyld</span><span class="o">::</span><span class="n">SymbolInfo</span><span class="p">(</span><span class="n">nullptr</span><span class="p">);</span>
+        <span class="p">});</span>
+
+    <span class="c1">// Build a singlton module set to hold our module.</span>
+    <span class="n">std</span><span class="o">::</span><span class="n">vector</span><span class="o"><</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">>></span> <span class="n">Ms</span><span class="p">;</span>
+    <span class="n">Ms</span><span class="p">.</span><span class="n">push_back</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">M</span><span class="p">));</span>
+
+    <span class="c1">// Add the set to the JIT with the resolver we created above and a newly</span>
+    <span class="c1">// created SectionMemoryManager.</span>
+    <span class="k">return</span> <span class="n">CODLayer</span><span class="p">.</span><span class="n">addModuleSet</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Ms</span><span class="p">),</span>
+                                 <span class="n">make_unique</span><span class="o"><</span><span class="n">SectionMemoryManager</span><span class="o">></span><span class="p">(),</span>
+                                 <span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Resolver</span><span class="p">));</span>
+  <span class="p">}</span>
+
+  <span class="n">JITSymbol</span> <span class="n">findSymbol</span><span class="p">(</span><span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="n">Name</span><span class="p">)</span> <span class="p">{</span>
+    <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="n">MangledName</span><span class="p">;</span>
+    <span class="n">raw_string_ostream</span> <span class="nf">MangledNameStream</span><span class="p">(</span><span class="n">MangledName</span><span class="p">);</span>
+    <span class="n">Mangler</span><span class="o">::</span><span class="n">getNameWithPrefix</span><span class="p">(</span><span class="n">MangledNameStream</span><span class="p">,</span> <span class="n">Name</span><span class="p">,</span> <span class="n">DL</span><span class="p">);</span>
+    <span class="k">return</span> <span class="n">CODLayer</span><span class="p">.</span><span class="n">findSymbol</span><span class="p">(</span><span class="n">MangledNameStream</span><span class="p">.</span><span class="n">str</span><span class="p">(),</span> <span class="nb">true</span><span class="p">);</span>
+  <span class="p">}</span>
+
+  <span class="kt">void</span> <span class="n">removeModule</span><span class="p">(</span><span class="n">ModuleHandle</span> <span class="n">H</span><span class="p">)</span> <span class="p">{</span>
+    <span class="n">CODLayer</span><span class="p">.</span><span class="n">removeModuleSet</span><span class="p">(</span><span class="n">H</span><span class="p">);</span>
+  <span class="p">}</span>
+
+<span class="nl">private:</span>
+
+  <span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span> <span class="n">optimizeModule</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span> <span class="n">M</span><span class="p">)</span> <span class="p">{</span>
+    <span class="c1">// Create a function pass manager.</span>
+    <span class="k">auto</span> <span class="n">FPM</span> <span class="o">=</span> <span class="n">llvm</span><span class="o">::</span><span class="n">make_unique</span><span class="o"><</span><span class="n">legacy</span><span class="o">::</span><span class="n">FunctionPassManager</span><span class="o">></span><span class="p">(</span><span class="n">M</span><span class="p">.</span><span class="n">get</span><span class="p">());</span>
+
+    <span class="c1">// Add some optimizations.</span>
+    <span class="n">FPM</span><span class="o">-></span><span class="n">add</span><span class="p">(</span><span class="n">createInstructionCombiningPass</span><span class="p">());</span>
+    <span class="n">FPM</span><span class="o">-></span><span class="n">add</span><span class="p">(</span><span class="n">createReassociatePass</span><span class="p">());</span>
+    <span class="n">FPM</span><span class="o">-></span><span class="n">add</span><span class="p">(</span><span class="n">createGVNPass</span><span class="p">());</span>
+    <span class="n">FPM</span><span class="o">-></span><span class="n">add</span><span class="p">(</span><span class="n">createCFGSimplificationPass</span><span class="p">());</span>
+    <span class="n">FPM</span><span class="o">-></span><span class="n">doInitialization</span><span class="p">();</span>
+
+    <span class="c1">// Run the optimizations over all functions in the module being added to</span>
+    <span class="c1">// the JIT.</span>
+    <span class="k">for</span> <span class="p">(</span><span class="k">auto</span> <span class="o">&</span><span class="n">F</span> <span class="o">:</span> <span class="o">*</span><span class="n">M</span><span class="p">)</span>
+      <span class="n">FPM</span><span class="o">-></span><span class="n">run</span><span class="p">(</span><span class="n">F</span><span class="p">);</span>
+
+    <span class="k">return</span> <span class="n">M</span><span class="p">;</span>
+  <span class="p">}</span>
+
+<span class="p">};</span>
+
+<span class="p">}</span> <span class="c1">// end namespace orc</span>
+<span class="p">}</span> <span class="c1">// end namespace llvm</span>
+
+<span class="cp">#endif </span><span class="c1">// LLVM_EXECUTIONENGINE_ORC_KALEIDOSCOPEJIT_H</span>
+</pre></div>
+</div>
+<p><a class="reference external" href="BuildingAJIT4.html">Next: Extreme Laziness – Using Compile Callbacks to JIT directly from ASTs</a></p>
+</div>
+</div>
+
+
+          </div>
+      </div>
+      <div class="clearer"></div>
+    </div>
+    <div class="related">
+      <h3>Navigation</h3>
+      <ul>
+        <li class="right" style="margin-right: 10px">
+          <a href="../genindex.html" title="General Index"
+             >index</a></li>
+        <li class="right" >
+          <a href="BuildingAJIT4.html" title="4. Building a JIT: Extreme Laziness - Using Compile Callbacks to JIT from ASTs"
+             >next</a> |</li>
+        <li class="right" >
+          <a href="BuildingAJIT2.html" title="2. Building a JIT: Adding Optimizations – An introduction to ORC Layers"
+             >previous</a> |</li>
+  <li><a href="http://llvm.org/">LLVM Home</a> | </li>
+  <li><a href="../index.html">Documentation</a>»</li>
+
+          <li><a href="index.html" >LLVM Tutorial: Table of Contents</a> »</li> 
+      </ul>
+    </div>
+    <div class="footer">
+        © Copyright 2003-2016, LLVM Project.
+      Last updated on 2016-12-21.
+      Created using <a href="http://sphinx-doc.org/">Sphinx</a> 1.2.2.
+    </div>
+  </body>
+</html>
\ No newline at end of file

Added: www-releases/trunk/3.9.1/docs/tutorial/BuildingAJIT4.html
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/tutorial/BuildingAJIT4.html?rev=290368&view=auto
==============================================================================
--- www-releases/trunk/3.9.1/docs/tutorial/BuildingAJIT4.html (added)
+++ www-releases/trunk/3.9.1/docs/tutorial/BuildingAJIT4.html Thu Dec 22 14:04:03 2016
@@ -0,0 +1,370 @@
+
+<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN"
+  "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd">
+
+
+<html xmlns="http://www.w3.org/1999/xhtml">
+  <head>
+    <meta http-equiv="Content-Type" content="text/html; charset=utf-8" />
+    
+    <title>4. Building a JIT: Extreme Laziness - Using Compile Callbacks to JIT from ASTs — LLVM 3.9 documentation</title>
+    
+    <link rel="stylesheet" href="../_static/llvm-theme.css" type="text/css" />
+    <link rel="stylesheet" href="../_static/pygments.css" type="text/css" />
+    
+    <script type="text/javascript">
+      var DOCUMENTATION_OPTIONS = {
+        URL_ROOT:    '../',
+        VERSION:     '3.9',
+        COLLAPSE_INDEX: false,
+        FILE_SUFFIX: '.html',
+        HAS_SOURCE:  true
+      };
+    </script>
+    <script type="text/javascript" src="../_static/jquery.js"></script>
+    <script type="text/javascript" src="../_static/underscore.js"></script>
+    <script type="text/javascript" src="../_static/doctools.js"></script>
+    <link rel="top" title="LLVM 3.9 documentation" href="../index.html" />
+    <link rel="up" title="LLVM Tutorial: Table of Contents" href="index.html" />
+    <link rel="next" title="5. Building a JIT: Remote-JITing – Process Isolation and Laziness at a Distance" href="BuildingAJIT5.html" />
+    <link rel="prev" title="3. Building a JIT: Per-function Lazy Compilation" href="BuildingAJIT3.html" />
+<style type="text/css">
+  table.right { float: right; margin-left: 20px; }
+  table.right td { border: 1px solid #ccc; }
+</style>
+
+  </head>
+  <body>
+<div class="logo">
+  <a href="../index.html">
+    <img src="../_static/logo.png"
+         alt="LLVM Logo" width="250" height="88"/></a>
+</div>
+
+    <div class="related">
+      <h3>Navigation</h3>
+      <ul>
+        <li class="right" style="margin-right: 10px">
+          <a href="../genindex.html" title="General Index"
+             accesskey="I">index</a></li>
+        <li class="right" >
+          <a href="BuildingAJIT5.html" title="5. Building a JIT: Remote-JITing – Process Isolation and Laziness at a Distance"
+             accesskey="N">next</a> |</li>
+        <li class="right" >
+          <a href="BuildingAJIT3.html" title="3. Building a JIT: Per-function Lazy Compilation"
+             accesskey="P">previous</a> |</li>
+  <li><a href="http://llvm.org/">LLVM Home</a> | </li>
+  <li><a href="../index.html">Documentation</a>»</li>
+
+          <li><a href="index.html" accesskey="U">LLVM Tutorial: Table of Contents</a> »</li> 
+      </ul>
+    </div>
+
+
+    <div class="document">
+      <div class="documentwrapper">
+          <div class="body">
+            
+  <div class="section" id="building-a-jit-extreme-laziness-using-compile-callbacks-to-jit-from-asts">
+<h1>4. Building a JIT: Extreme Laziness - Using Compile Callbacks to JIT from ASTs<a class="headerlink" href="#building-a-jit-extreme-laziness-using-compile-callbacks-to-jit-from-asts" title="Permalink to this headline">¶</a></h1>
+<div class="contents local topic" id="contents">
+<ul class="simple">
+<li><a class="reference internal" href="#chapter-4-introduction" id="id1">Chapter 4 Introduction</a></li>
+<li><a class="reference internal" href="#full-code-listing" id="id2">Full Code Listing</a></li>
+</ul>
+</div>
+<p><strong>This tutorial is under active development. It is incomplete and details may
+change frequently.</strong> Nonetheless we invite you to try it out as it stands, and
+we welcome any feedback.</p>
+<div class="section" id="chapter-4-introduction">
+<h2><a class="toc-backref" href="#id1">4.1. Chapter 4 Introduction</a><a class="headerlink" href="#chapter-4-introduction" title="Permalink to this headline">¶</a></h2>
+<p>Welcome to Chapter 4 of the “Building an ORC-based JIT in LLVM” tutorial. This
+chapter introduces the Compile Callbacks and Indirect Stubs APIs and shows how
+they can be used to replace the CompileOnDemand layer from
+<a class="reference external" href="BuildingAJIT3.html">Chapter 3</a> with a custom lazy-JITing scheme that JITs
+directly from Kaleidoscope ASTs.</p>
+<p><strong>To be done:</strong></p>
+<p><strong>(1) Describe the drawbacks of JITing from IR (have to compile to IR first,
+which reduces the benefits of laziness).</strong></p>
+<p><strong>(2) Describe CompileCallbackManagers and IndirectStubManagers in detail.</strong></p>
+<p><strong>(3) Run through the implementation of addFunctionAST.</strong></p>
+</div>
+<div class="section" id="full-code-listing">
+<h2><a class="toc-backref" href="#id2">4.2. Full Code Listing</a><a class="headerlink" href="#full-code-listing" title="Permalink to this headline">¶</a></h2>
+<p>Here is the complete code listing for our running example that JITs lazily from
+Kaleidoscope ASTS. To build this example, use:</p>
+<div class="highlight-bash"><div class="highlight"><pre><span class="c"># Compile</span>
+clang++ -g toy.cpp <span class="sb">`</span>llvm-config --cxxflags --ldflags --system-libs --libs core orc native<span class="sb">`</span> -O3 -o toy
+<span class="c"># Run</span>
+./toy
+</pre></div>
+</div>
+<p>Here is the code:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">//===----- KaleidoscopeJIT.h - A simple JIT for Kaleidoscope ----*- C++ -*-===//</span>
+<span class="c1">//</span>
+<span class="c1">//                     The LLVM Compiler Infrastructure</span>
+<span class="c1">//</span>
+<span class="c1">// This file is distributed under the University of Illinois Open Source</span>
+<span class="c1">// License. See LICENSE.TXT for details.</span>
+<span class="c1">//</span>
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+<span class="c1">//</span>
+<span class="c1">// Contains a simple JIT definition for use in the kaleidoscope tutorials.</span>
+<span class="c1">//</span>
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+
+<span class="cp">#ifndef LLVM_EXECUTIONENGINE_ORC_KALEIDOSCOPEJIT_H</span>
+<span class="cp">#define LLVM_EXECUTIONENGINE_ORC_KALEIDOSCOPEJIT_H</span>
+
+<span class="cp">#include "llvm/ADT/STLExtras.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/ExecutionEngine.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/RuntimeDyld.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/SectionMemoryManager.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/CompileOnDemandLayer.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/CompileUtils.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/JITSymbol.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/IRCompileLayer.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/IRTransformLayer.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/LambdaResolver.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/ObjectLinkingLayer.h"</span>
+<span class="cp">#include "llvm/IR/DataLayout.h"</span>
+<span class="cp">#include "llvm/IR/Mangler.h"</span>
+<span class="cp">#include "llvm/Support/DynamicLibrary.h"</span>
+<span class="cp">#include "llvm/Support/raw_ostream.h"</span>
+<span class="cp">#include "llvm/Target/TargetMachine.h"</span>
+<span class="cp">#include <algorithm></span>
+<span class="cp">#include <memory></span>
+<span class="cp">#include <string></span>
+<span class="cp">#include <vector></span>
+
+<span class="k">class</span> <span class="nc">PrototypeAST</span><span class="p">;</span>
+<span class="k">class</span> <span class="nc">ExprAST</span><span class="p">;</span>
+
+<span class="c1">/// FunctionAST - This class represents a function definition itself.</span>
+<span class="k">class</span> <span class="nc">FunctionAST</span> <span class="p">{</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">PrototypeAST</span><span class="o">></span> <span class="n">Proto</span><span class="p">;</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">ExprAST</span><span class="o">></span> <span class="n">Body</span><span class="p">;</span>
+
+<span class="nl">public:</span>
+  <span class="n">FunctionAST</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">PrototypeAST</span><span class="o">></span> <span class="n">Proto</span><span class="p">,</span>
+              <span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">ExprAST</span><span class="o">></span> <span class="n">Body</span><span class="p">)</span>
+      <span class="o">:</span> <span class="n">Proto</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Proto</span><span class="p">)),</span> <span class="n">Body</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Body</span><span class="p">))</span> <span class="p">{}</span>
+  <span class="k">const</span> <span class="n">PrototypeAST</span><span class="o">&</span> <span class="n">getProto</span><span class="p">()</span> <span class="k">const</span><span class="p">;</span>
+  <span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span><span class="o">&</span> <span class="n">getName</span><span class="p">()</span> <span class="k">const</span><span class="p">;</span>
+  <span class="n">llvm</span><span class="o">::</span><span class="n">Function</span> <span class="o">*</span><span class="n">codegen</span><span class="p">();</span>
+<span class="p">};</span>
+
+<span class="c1">/// This will compile FnAST to IR, rename the function to add the given</span>
+<span class="c1">/// suffix (needed to prevent a name-clash with the function's stub),</span>
+<span class="c1">/// and then take ownership of the module that the function was compiled</span>
+<span class="c1">/// into.</span>
+<span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">llvm</span><span class="o">::</span><span class="n">Module</span><span class="o">></span>
+<span class="n">irgenAndTakeOwnership</span><span class="p">(</span><span class="n">FunctionAST</span> <span class="o">&</span><span class="n">FnAST</span><span class="p">,</span> <span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="o">&</span><span class="n">Suffix</span><span class="p">);</span>
+
+<span class="k">namespace</span> <span class="n">llvm</span> <span class="p">{</span>
+<span class="k">namespace</span> <span class="n">orc</span> <span class="p">{</span>
+
+<span class="k">class</span> <span class="nc">KaleidoscopeJIT</span> <span class="p">{</span>
+<span class="nl">private:</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">TargetMachine</span><span class="o">></span> <span class="n">TM</span><span class="p">;</span>
+  <span class="k">const</span> <span class="n">DataLayout</span> <span class="n">DL</span><span class="p">;</span>
+  <span class="n">ObjectLinkingLayer</span><span class="o"><></span> <span class="n">ObjectLayer</span><span class="p">;</span>
+  <span class="n">IRCompileLayer</span><span class="o"><</span><span class="n">decltype</span><span class="p">(</span><span class="n">ObjectLayer</span><span class="p">)</span><span class="o">></span> <span class="n">CompileLayer</span><span class="p">;</span>
+
+  <span class="k">typedef</span> <span class="n">std</span><span class="o">::</span><span class="n">function</span><span class="o"><</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span><span class="p">)</span><span class="o">></span>
+    <span class="n">OptimizeFunction</span><span class="p">;</span>
+
+  <span class="n">IRTransformLayer</span><span class="o"><</span><span class="n">decltype</span><span class="p">(</span><span class="n">CompileLayer</span><span class="p">),</span> <span class="n">OptimizeFunction</span><span class="o">></span> <span class="n">OptimizeLayer</span><span class="p">;</span>
+
+  <span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">JITCompileCallbackManager</span><span class="o">></span> <span class="n">CompileCallbackMgr</span><span class="p">;</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">IndirectStubsManager</span><span class="o">></span> <span class="n">IndirectStubsMgr</span><span class="p">;</span>
+
+<span class="nl">public:</span>
+  <span class="k">typedef</span> <span class="n">decltype</span><span class="p">(</span><span class="n">OptimizeLayer</span><span class="p">)</span><span class="o">::</span><span class="n">ModuleSetHandleT</span> <span class="n">ModuleHandle</span><span class="p">;</span>
+
+  <span class="n">KaleidoscopeJIT</span><span class="p">()</span>
+      <span class="o">:</span> <span class="n">TM</span><span class="p">(</span><span class="n">EngineBuilder</span><span class="p">().</span><span class="n">selectTarget</span><span class="p">()),</span>
+        <span class="n">DL</span><span class="p">(</span><span class="n">TM</span><span class="o">-></span><span class="n">createDataLayout</span><span class="p">()),</span>
+        <span class="n">CompileLayer</span><span class="p">(</span><span class="n">ObjectLayer</span><span class="p">,</span> <span class="n">SimpleCompiler</span><span class="p">(</span><span class="o">*</span><span class="n">TM</span><span class="p">)),</span>
+        <span class="n">OptimizeLayer</span><span class="p">(</span><span class="n">CompileLayer</span><span class="p">,</span>
+                      <span class="p">[</span><span class="k">this</span><span class="p">](</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span> <span class="n">M</span><span class="p">)</span> <span class="p">{</span>
+                        <span class="k">return</span> <span class="n">optimizeModule</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">M</span><span class="p">));</span>
+                      <span class="p">}),</span>
+        <span class="n">CompileCallbackMgr</span><span class="p">(</span>
+            <span class="n">orc</span><span class="o">::</span><span class="n">createLocalCompileCallbackManager</span><span class="p">(</span><span class="n">TM</span><span class="o">-></span><span class="n">getTargetTriple</span><span class="p">(),</span> <span class="mi">0</span><span class="p">))</span> <span class="p">{</span>
+    <span class="k">auto</span> <span class="n">IndirectStubsMgrBuilder</span> <span class="o">=</span>
+      <span class="n">orc</span><span class="o">::</span><span class="n">createLocalIndirectStubsManagerBuilder</span><span class="p">(</span><span class="n">TM</span><span class="o">-></span><span class="n">getTargetTriple</span><span class="p">());</span>
+    <span class="n">IndirectStubsMgr</span> <span class="o">=</span> <span class="n">IndirectStubsMgrBuilder</span><span class="p">();</span>
+    <span class="n">llvm</span><span class="o">::</span><span class="n">sys</span><span class="o">::</span><span class="n">DynamicLibrary</span><span class="o">::</span><span class="n">LoadLibraryPermanently</span><span class="p">(</span><span class="n">nullptr</span><span class="p">);</span>
+  <span class="p">}</span>
+
+  <span class="n">TargetMachine</span> <span class="o">&</span><span class="n">getTargetMachine</span><span class="p">()</span> <span class="p">{</span> <span class="k">return</span> <span class="o">*</span><span class="n">TM</span><span class="p">;</span> <span class="p">}</span>
+
+  <span class="n">ModuleHandle</span> <span class="n">addModule</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span> <span class="n">M</span><span class="p">)</span> <span class="p">{</span>
+
+    <span class="c1">// Build our symbol resolver:</span>
+    <span class="c1">// Lambda 1: Look back into the JIT itself to find symbols that are part of</span>
+    <span class="c1">//           the same "logical dylib".</span>
+    <span class="c1">// Lambda 2: Search for external symbols in the host process.</span>
+    <span class="k">auto</span> <span class="n">Resolver</span> <span class="o">=</span> <span class="n">createLambdaResolver</span><span class="p">(</span>
+        <span class="p">[</span><span class="o">&</span><span class="p">](</span><span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="o">&</span><span class="n">Name</span><span class="p">)</span> <span class="p">{</span>
+          <span class="k">if</span> <span class="p">(</span><span class="k">auto</span> <span class="n">Sym</span> <span class="o">=</span> <span class="n">IndirectStubsMgr</span><span class="o">-></span><span class="n">findStub</span><span class="p">(</span><span class="n">Name</span><span class="p">,</span> <span class="nb">false</span><span class="p">))</span>
+            <span class="k">return</span> <span class="n">Sym</span><span class="p">.</span><span class="n">toRuntimeDyldSymbol</span><span class="p">();</span>
+          <span class="k">if</span> <span class="p">(</span><span class="k">auto</span> <span class="n">Sym</span> <span class="o">=</span> <span class="n">OptimizeLayer</span><span class="p">.</span><span class="n">findSymbol</span><span class="p">(</span><span class="n">Name</span><span class="p">,</span> <span class="nb">false</span><span class="p">))</span>
+            <span class="k">return</span> <span class="n">Sym</span><span class="p">.</span><span class="n">toRuntimeDyldSymbol</span><span class="p">();</span>
+          <span class="k">return</span> <span class="n">RuntimeDyld</span><span class="o">::</span><span class="n">SymbolInfo</span><span class="p">(</span><span class="n">nullptr</span><span class="p">);</span>
+        <span class="p">},</span>
+        <span class="p">[](</span><span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="o">&</span><span class="n">Name</span><span class="p">)</span> <span class="p">{</span>
+          <span class="k">if</span> <span class="p">(</span><span class="k">auto</span> <span class="n">SymAddr</span> <span class="o">=</span>
+                <span class="n">RTDyldMemoryManager</span><span class="o">::</span><span class="n">getSymbolAddressInProcess</span><span class="p">(</span><span class="n">Name</span><span class="p">))</span>
+            <span class="k">return</span> <span class="n">RuntimeDyld</span><span class="o">::</span><span class="n">SymbolInfo</span><span class="p">(</span><span class="n">SymAddr</span><span class="p">,</span> <span class="n">JITSymbolFlags</span><span class="o">::</span><span class="n">Exported</span><span class="p">);</span>
+          <span class="k">return</span> <span class="n">RuntimeDyld</span><span class="o">::</span><span class="n">SymbolInfo</span><span class="p">(</span><span class="n">nullptr</span><span class="p">);</span>
+        <span class="p">});</span>
+
+    <span class="c1">// Build a singlton module set to hold our module.</span>
+    <span class="n">std</span><span class="o">::</span><span class="n">vector</span><span class="o"><</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">>></span> <span class="n">Ms</span><span class="p">;</span>
+    <span class="n">Ms</span><span class="p">.</span><span class="n">push_back</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">M</span><span class="p">));</span>
+
+    <span class="c1">// Add the set to the JIT with the resolver we created above and a newly</span>
+    <span class="c1">// created SectionMemoryManager.</span>
+    <span class="k">return</span> <span class="n">OptimizeLayer</span><span class="p">.</span><span class="n">addModuleSet</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Ms</span><span class="p">),</span>
+                                      <span class="n">make_unique</span><span class="o"><</span><span class="n">SectionMemoryManager</span><span class="o">></span><span class="p">(),</span>
+                                      <span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Resolver</span><span class="p">));</span>
+  <span class="p">}</span>
+
+  <span class="n">Error</span> <span class="n">addFunctionAST</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">FunctionAST</span><span class="o">></span> <span class="n">FnAST</span><span class="p">)</span> <span class="p">{</span>
+    <span class="c1">// Create a CompileCallback - this is the re-entry point into the compiler</span>
+    <span class="c1">// for functions that haven't been compiled yet.</span>
+    <span class="k">auto</span> <span class="n">CCInfo</span> <span class="o">=</span> <span class="n">CompileCallbackMgr</span><span class="o">-></span><span class="n">getCompileCallback</span><span class="p">();</span>
+
+    <span class="c1">// Create an indirect stub. This serves as the functions "canonical</span>
+    <span class="c1">// definition" - an unchanging (constant address) entry point to the</span>
+    <span class="c1">// function implementation.</span>
+    <span class="c1">// Initially we point the stub's function-pointer at the compile callback</span>
+    <span class="c1">// that we just created. In the compile action for the callback (see below)</span>
+    <span class="c1">// we will update the stub's function pointer to point at the function</span>
+    <span class="c1">// implementation that we just implemented.</span>
+    <span class="k">if</span> <span class="p">(</span><span class="k">auto</span> <span class="n">Err</span> <span class="o">=</span> <span class="n">IndirectStubsMgr</span><span class="o">-></span><span class="n">createStub</span><span class="p">(</span><span class="n">mangle</span><span class="p">(</span><span class="n">FnAST</span><span class="o">-></span><span class="n">getName</span><span class="p">()),</span>
+                                                <span class="n">CCInfo</span><span class="p">.</span><span class="n">getAddress</span><span class="p">(),</span>
+                                                <span class="n">JITSymbolFlags</span><span class="o">::</span><span class="n">Exported</span><span class="p">))</span>
+      <span class="k">return</span> <span class="n">Err</span><span class="p">;</span>
+
+    <span class="c1">// Move ownership of FnAST to a shared pointer - C++11 lambdas don't support</span>
+    <span class="c1">// capture-by-move, which is be required for unique_ptr.</span>
+    <span class="k">auto</span> <span class="n">SharedFnAST</span> <span class="o">=</span> <span class="n">std</span><span class="o">::</span><span class="n">shared_ptr</span><span class="o"><</span><span class="n">FunctionAST</span><span class="o">></span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">FnAST</span><span class="p">));</span>
+
+    <span class="c1">// Set the action to compile our AST. This lambda will be run if/when</span>
+    <span class="c1">// execution hits the compile callback (via the stub).</span>
+    <span class="c1">//</span>
+    <span class="c1">// The steps to compile are:</span>
+    <span class="c1">// (1) IRGen the function.</span>
+    <span class="c1">// (2) Add the IR module to the JIT to make it executable like any other</span>
+    <span class="c1">//     module.</span>
+    <span class="c1">// (3) Use findSymbol to get the address of the compiled function.</span>
+    <span class="c1">// (4) Update the stub pointer to point at the implementation so that</span>
+    <span class="c1">///    subsequent calls go directly to it and bypass the compiler.</span>
+    <span class="c1">// (5) Return the address of the implementation: this lambda will actually</span>
+    <span class="c1">//     be run inside an attempted call to the function, and we need to</span>
+    <span class="c1">//     continue on to the implementation to complete the attempted call.</span>
+    <span class="c1">//     The JIT runtime (the resolver block) will use the return address of</span>
+    <span class="c1">//     this function as the address to continue at once it has reset the</span>
+    <span class="c1">//     CPU state to what it was immediately before the call.</span>
+    <span class="n">CCInfo</span><span class="p">.</span><span class="n">setCompileAction</span><span class="p">(</span>
+      <span class="p">[</span><span class="k">this</span><span class="p">,</span> <span class="n">SharedFnAST</span><span class="p">]()</span> <span class="p">{</span>
+        <span class="k">auto</span> <span class="n">M</span> <span class="o">=</span> <span class="n">irgenAndTakeOwnership</span><span class="p">(</span><span class="o">*</span><span class="n">SharedFnAST</span><span class="p">,</span> <span class="s">"$impl"</span><span class="p">);</span>
+        <span class="n">addModule</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">M</span><span class="p">));</span>
+        <span class="k">auto</span> <span class="n">Sym</span> <span class="o">=</span> <span class="n">findSymbol</span><span class="p">(</span><span class="n">SharedFnAST</span><span class="o">-></span><span class="n">getName</span><span class="p">()</span> <span class="o">+</span> <span class="s">"$impl"</span><span class="p">);</span>
+        <span class="n">assert</span><span class="p">(</span><span class="n">Sym</span> <span class="o">&&</span> <span class="s">"Couldn't find compiled function?"</span><span class="p">);</span>
+        <span class="n">TargetAddress</span> <span class="n">SymAddr</span> <span class="o">=</span> <span class="n">Sym</span><span class="p">.</span><span class="n">getAddress</span><span class="p">();</span>
+        <span class="k">if</span> <span class="p">(</span><span class="k">auto</span> <span class="n">Err</span> <span class="o">=</span>
+              <span class="n">IndirectStubsMgr</span><span class="o">-></span><span class="n">updatePointer</span><span class="p">(</span><span class="n">mangle</span><span class="p">(</span><span class="n">SharedFnAST</span><span class="o">-></span><span class="n">getName</span><span class="p">()),</span>
+                                              <span class="n">SymAddr</span><span class="p">))</span> <span class="p">{</span>
+          <span class="n">logAllUnhandledErrors</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Err</span><span class="p">),</span> <span class="n">errs</span><span class="p">(),</span>
+                                <span class="s">"Error updating function pointer: "</span><span class="p">);</span>
+          <span class="n">exit</span><span class="p">(</span><span class="mi">1</span><span class="p">);</span>
+        <span class="p">}</span>
+
+        <span class="k">return</span> <span class="n">SymAddr</span><span class="p">;</span>
+      <span class="p">});</span>
+
+    <span class="k">return</span> <span class="n">Error</span><span class="o">::</span><span class="n">success</span><span class="p">();</span>
+  <span class="p">}</span>
+
+  <span class="n">JITSymbol</span> <span class="n">findSymbol</span><span class="p">(</span><span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="n">Name</span><span class="p">)</span> <span class="p">{</span>
+    <span class="k">return</span> <span class="n">OptimizeLayer</span><span class="p">.</span><span class="n">findSymbol</span><span class="p">(</span><span class="n">mangle</span><span class="p">(</span><span class="n">Name</span><span class="p">),</span> <span class="nb">true</span><span class="p">);</span>
+  <span class="p">}</span>
+
+  <span class="kt">void</span> <span class="n">removeModule</span><span class="p">(</span><span class="n">ModuleHandle</span> <span class="n">H</span><span class="p">)</span> <span class="p">{</span>
+    <span class="n">OptimizeLayer</span><span class="p">.</span><span class="n">removeModuleSet</span><span class="p">(</span><span class="n">H</span><span class="p">);</span>
+  <span class="p">}</span>
+
+<span class="nl">private:</span>
+
+  <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="n">mangle</span><span class="p">(</span><span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="o">&</span><span class="n">Name</span><span class="p">)</span> <span class="p">{</span>
+    <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="n">MangledName</span><span class="p">;</span>
+    <span class="n">raw_string_ostream</span> <span class="nf">MangledNameStream</span><span class="p">(</span><span class="n">MangledName</span><span class="p">);</span>
+    <span class="n">Mangler</span><span class="o">::</span><span class="n">getNameWithPrefix</span><span class="p">(</span><span class="n">MangledNameStream</span><span class="p">,</span> <span class="n">Name</span><span class="p">,</span> <span class="n">DL</span><span class="p">);</span>
+    <span class="k">return</span> <span class="n">MangledNameStream</span><span class="p">.</span><span class="n">str</span><span class="p">();</span>
+  <span class="p">}</span>
+
+  <span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span> <span class="n">optimizeModule</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span> <span class="n">M</span><span class="p">)</span> <span class="p">{</span>
+    <span class="c1">// Create a function pass manager.</span>
+    <span class="k">auto</span> <span class="n">FPM</span> <span class="o">=</span> <span class="n">llvm</span><span class="o">::</span><span class="n">make_unique</span><span class="o"><</span><span class="n">legacy</span><span class="o">::</span><span class="n">FunctionPassManager</span><span class="o">></span><span class="p">(</span><span class="n">M</span><span class="p">.</span><span class="n">get</span><span class="p">());</span>
+
+    <span class="c1">// Add some optimizations.</span>
+    <span class="n">FPM</span><span class="o">-></span><span class="n">add</span><span class="p">(</span><span class="n">createInstructionCombiningPass</span><span class="p">());</span>
+    <span class="n">FPM</span><span class="o">-></span><span class="n">add</span><span class="p">(</span><span class="n">createReassociatePass</span><span class="p">());</span>
+    <span class="n">FPM</span><span class="o">-></span><span class="n">add</span><span class="p">(</span><span class="n">createGVNPass</span><span class="p">());</span>
+    <span class="n">FPM</span><span class="o">-></span><span class="n">add</span><span class="p">(</span><span class="n">createCFGSimplificationPass</span><span class="p">());</span>
+    <span class="n">FPM</span><span class="o">-></span><span class="n">doInitialization</span><span class="p">();</span>
+
+    <span class="c1">// Run the optimizations over all functions in the module being added to</span>
+    <span class="c1">// the JIT.</span>
+    <span class="k">for</span> <span class="p">(</span><span class="k">auto</span> <span class="o">&</span><span class="n">F</span> <span class="o">:</span> <span class="o">*</span><span class="n">M</span><span class="p">)</span>
+      <span class="n">FPM</span><span class="o">-></span><span class="n">run</span><span class="p">(</span><span class="n">F</span><span class="p">);</span>
+
+    <span class="k">return</span> <span class="n">M</span><span class="p">;</span>
+  <span class="p">}</span>
+
+<span class="p">};</span>
+
+<span class="p">}</span> <span class="c1">// end namespace orc</span>
+<span class="p">}</span> <span class="c1">// end namespace llvm</span>
+
+<span class="cp">#endif </span><span class="c1">// LLVM_EXECUTIONENGINE_ORC_KALEIDOSCOPEJIT_H</span>
+</pre></div>
+</div>
+<p><a class="reference external" href="BuildingAJIT5.html">Next: Remote-JITing – Process-isolation and laziness-at-a-distance</a></p>
+</div>
+</div>
+
+
+          </div>
+      </div>
+      <div class="clearer"></div>
+    </div>
+    <div class="related">
+      <h3>Navigation</h3>
+      <ul>
+        <li class="right" style="margin-right: 10px">
+          <a href="../genindex.html" title="General Index"
+             >index</a></li>
+        <li class="right" >
+          <a href="BuildingAJIT5.html" title="5. Building a JIT: Remote-JITing – Process Isolation and Laziness at a Distance"
+             >next</a> |</li>
+        <li class="right" >
+          <a href="BuildingAJIT3.html" title="3. Building a JIT: Per-function Lazy Compilation"
+             >previous</a> |</li>
+  <li><a href="http://llvm.org/">LLVM Home</a> | </li>
+  <li><a href="../index.html">Documentation</a>»</li>
+
+          <li><a href="index.html" >LLVM Tutorial: Table of Contents</a> »</li> 
+      </ul>
+    </div>
+    <div class="footer">
+        © Copyright 2003-2016, LLVM Project.
+      Last updated on 2016-12-21.
+      Created using <a href="http://sphinx-doc.org/">Sphinx</a> 1.2.2.
+    </div>
+  </body>
+</html>
\ No newline at end of file

Added: www-releases/trunk/3.9.1/docs/tutorial/BuildingAJIT5.html
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/tutorial/BuildingAJIT5.html?rev=290368&view=auto
==============================================================================
--- www-releases/trunk/3.9.1/docs/tutorial/BuildingAJIT5.html (added)
+++ www-releases/trunk/3.9.1/docs/tutorial/BuildingAJIT5.html Thu Dec 22 14:04:03 2016
@@ -0,0 +1,526 @@
+
+<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN"
+  "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd">
+
+
+<html xmlns="http://www.w3.org/1999/xhtml">
+  <head>
+    <meta http-equiv="Content-Type" content="text/html; charset=utf-8" />
+    
+    <title>5. Building a JIT: Remote-JITing – Process Isolation and Laziness at a Distance — LLVM 3.9 documentation</title>
+    
+    <link rel="stylesheet" href="../_static/llvm-theme.css" type="text/css" />
+    <link rel="stylesheet" href="../_static/pygments.css" type="text/css" />
+    
+    <script type="text/javascript">
+      var DOCUMENTATION_OPTIONS = {
+        URL_ROOT:    '../',
+        VERSION:     '3.9',
+        COLLAPSE_INDEX: false,
+        FILE_SUFFIX: '.html',
+        HAS_SOURCE:  true
+      };
+    </script>
+    <script type="text/javascript" src="../_static/jquery.js"></script>
+    <script type="text/javascript" src="../_static/underscore.js"></script>
+    <script type="text/javascript" src="../_static/doctools.js"></script>
+    <link rel="top" title="LLVM 3.9 documentation" href="../index.html" />
+    <link rel="up" title="LLVM Tutorial: Table of Contents" href="index.html" />
+    <link rel="next" title="LLVM 3.9 Release Notes" href="../ReleaseNotes.html" />
+    <link rel="prev" title="4. Building a JIT: Extreme Laziness - Using Compile Callbacks to JIT from ASTs" href="BuildingAJIT4.html" />
+<style type="text/css">
+  table.right { float: right; margin-left: 20px; }
+  table.right td { border: 1px solid #ccc; }
+</style>
+
+  </head>
+  <body>
+<div class="logo">
+  <a href="../index.html">
+    <img src="../_static/logo.png"
+         alt="LLVM Logo" width="250" height="88"/></a>
+</div>
+
+    <div class="related">
+      <h3>Navigation</h3>
+      <ul>
+        <li class="right" style="margin-right: 10px">
+          <a href="../genindex.html" title="General Index"
+             accesskey="I">index</a></li>
+        <li class="right" >
+          <a href="../ReleaseNotes.html" title="LLVM 3.9 Release Notes"
+             accesskey="N">next</a> |</li>
+        <li class="right" >
+          <a href="BuildingAJIT4.html" title="4. Building a JIT: Extreme Laziness - Using Compile Callbacks to JIT from ASTs"
+             accesskey="P">previous</a> |</li>
+  <li><a href="http://llvm.org/">LLVM Home</a> | </li>
+  <li><a href="../index.html">Documentation</a>»</li>
+
+          <li><a href="index.html" accesskey="U">LLVM Tutorial: Table of Contents</a> »</li> 
+      </ul>
+    </div>
+
+
+    <div class="document">
+      <div class="documentwrapper">
+          <div class="body">
+            
+  <div class="section" id="building-a-jit-remote-jiting-process-isolation-and-laziness-at-a-distance">
+<h1>5. Building a JIT: Remote-JITing – Process Isolation and Laziness at a Distance<a class="headerlink" href="#building-a-jit-remote-jiting-process-isolation-and-laziness-at-a-distance" title="Permalink to this headline">¶</a></h1>
+<div class="contents local topic" id="contents">
+<ul class="simple">
+<li><a class="reference internal" href="#chapter-5-introduction" id="id1">Chapter 5 Introduction</a></li>
+<li><a class="reference internal" href="#full-code-listing" id="id2">Full Code Listing</a></li>
+</ul>
+</div>
+<p><strong>This tutorial is under active development. It is incomplete and details may
+change frequently.</strong> Nonetheless we invite you to try it out as it stands, and
+we welcome any feedback.</p>
+<div class="section" id="chapter-5-introduction">
+<h2><a class="toc-backref" href="#id1">5.1. Chapter 5 Introduction</a><a class="headerlink" href="#chapter-5-introduction" title="Permalink to this headline">¶</a></h2>
+<p>Welcome to Chapter 5 of the “Building an ORC-based JIT in LLVM” tutorial. This
+chapter introduces the ORC RemoteJIT Client/Server APIs and shows how to use
+them to build a JIT stack that will execute its code via a communications
+channel with a different process. This can be a separate process on the same
+machine, a process on a different machine, or even a process on a different
+platform/architecture. The code builds on top of the lazy-AST-compiling JIT
+stack from <a class="reference external" href="BuildingAJIT3.html">Chapter 4</a>.</p>
+<p><strong>To be done – this is going to be a long one:</strong></p>
+<p><strong>(1) Introduce channels, RPC, RemoteJIT Client and Server APIs</strong></p>
+<p><strong>(2) Describe the client code in greater detail. Discuss modifications of the
+KaleidoscopeJIT class, and the REPL itself.</strong></p>
+<p><strong>(3) Describe the server code.</strong></p>
+<p><strong>(4) Describe how to run the demo.</strong></p>
+</div>
+<div class="section" id="full-code-listing">
+<h2><a class="toc-backref" href="#id2">5.2. Full Code Listing</a><a class="headerlink" href="#full-code-listing" title="Permalink to this headline">¶</a></h2>
+<p>Here is the complete code listing for our running example that JITs lazily from
+Kaleidoscope ASTS. To build this example, use:</p>
+<div class="highlight-bash"><div class="highlight"><pre><span class="c"># Compile</span>
+clang++ -g toy.cpp <span class="sb">`</span>llvm-config --cxxflags --ldflags --system-libs --libs core orc native<span class="sb">`</span> -O3 -o toy
+<span class="c"># Run</span>
+./toy
+</pre></div>
+</div>
+<p>Here is the code for the modified KaleidoscopeJIT:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">//===----- KaleidoscopeJIT.h - A simple JIT for Kaleidoscope ----*- C++ -*-===//</span>
+<span class="c1">//</span>
+<span class="c1">//                     The LLVM Compiler Infrastructure</span>
+<span class="c1">//</span>
+<span class="c1">// This file is distributed under the University of Illinois Open Source</span>
+<span class="c1">// License. See LICENSE.TXT for details.</span>
+<span class="c1">//</span>
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+<span class="c1">//</span>
+<span class="c1">// Contains a simple JIT definition for use in the kaleidoscope tutorials.</span>
+<span class="c1">//</span>
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+
+<span class="cp">#ifndef LLVM_EXECUTIONENGINE_ORC_KALEIDOSCOPEJIT_H</span>
+<span class="cp">#define LLVM_EXECUTIONENGINE_ORC_KALEIDOSCOPEJIT_H</span>
+
+<span class="cp">#include "RemoteJITUtils.h"</span>
+<span class="cp">#include "llvm/ADT/STLExtras.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/ExecutionEngine.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/RuntimeDyld.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/SectionMemoryManager.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/CompileOnDemandLayer.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/CompileUtils.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/JITSymbol.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/IRCompileLayer.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/IRTransformLayer.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/LambdaResolver.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/ObjectLinkingLayer.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/OrcRemoteTargetClient.h"</span>
+<span class="cp">#include "llvm/IR/DataLayout.h"</span>
+<span class="cp">#include "llvm/IR/Mangler.h"</span>
+<span class="cp">#include "llvm/Support/DynamicLibrary.h"</span>
+<span class="cp">#include "llvm/Support/raw_ostream.h"</span>
+<span class="cp">#include "llvm/Target/TargetMachine.h"</span>
+<span class="cp">#include <algorithm></span>
+<span class="cp">#include <memory></span>
+<span class="cp">#include <string></span>
+<span class="cp">#include <vector></span>
+
+<span class="k">class</span> <span class="nc">PrototypeAST</span><span class="p">;</span>
+<span class="k">class</span> <span class="nc">ExprAST</span><span class="p">;</span>
+
+<span class="c1">/// FunctionAST - This class represents a function definition itself.</span>
+<span class="k">class</span> <span class="nc">FunctionAST</span> <span class="p">{</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">PrototypeAST</span><span class="o">></span> <span class="n">Proto</span><span class="p">;</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">ExprAST</span><span class="o">></span> <span class="n">Body</span><span class="p">;</span>
+
+<span class="nl">public:</span>
+  <span class="n">FunctionAST</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">PrototypeAST</span><span class="o">></span> <span class="n">Proto</span><span class="p">,</span>
+              <span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">ExprAST</span><span class="o">></span> <span class="n">Body</span><span class="p">)</span>
+      <span class="o">:</span> <span class="n">Proto</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Proto</span><span class="p">)),</span> <span class="n">Body</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Body</span><span class="p">))</span> <span class="p">{}</span>
+  <span class="k">const</span> <span class="n">PrototypeAST</span><span class="o">&</span> <span class="n">getProto</span><span class="p">()</span> <span class="k">const</span><span class="p">;</span>
+  <span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span><span class="o">&</span> <span class="n">getName</span><span class="p">()</span> <span class="k">const</span><span class="p">;</span>
+  <span class="n">llvm</span><span class="o">::</span><span class="n">Function</span> <span class="o">*</span><span class="n">codegen</span><span class="p">();</span>
+<span class="p">};</span>
+
+<span class="c1">/// This will compile FnAST to IR, rename the function to add the given</span>
+<span class="c1">/// suffix (needed to prevent a name-clash with the function's stub),</span>
+<span class="c1">/// and then take ownership of the module that the function was compiled</span>
+<span class="c1">/// into.</span>
+<span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">llvm</span><span class="o">::</span><span class="n">Module</span><span class="o">></span>
+<span class="n">irgenAndTakeOwnership</span><span class="p">(</span><span class="n">FunctionAST</span> <span class="o">&</span><span class="n">FnAST</span><span class="p">,</span> <span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="o">&</span><span class="n">Suffix</span><span class="p">);</span>
+
+<span class="k">namespace</span> <span class="n">llvm</span> <span class="p">{</span>
+<span class="k">namespace</span> <span class="n">orc</span> <span class="p">{</span>
+
+<span class="c1">// Typedef the remote-client API.</span>
+<span class="k">typedef</span> <span class="n">remote</span><span class="o">::</span><span class="n">OrcRemoteTargetClient</span><span class="o"><</span><span class="n">FDRPCChannel</span><span class="o">></span> <span class="n">MyRemote</span><span class="p">;</span>
+
+<span class="k">class</span> <span class="nc">KaleidoscopeJIT</span> <span class="p">{</span>
+<span class="nl">private:</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">TargetMachine</span><span class="o">></span> <span class="n">TM</span><span class="p">;</span>
+  <span class="k">const</span> <span class="n">DataLayout</span> <span class="n">DL</span><span class="p">;</span>
+  <span class="n">ObjectLinkingLayer</span><span class="o"><></span> <span class="n">ObjectLayer</span><span class="p">;</span>
+  <span class="n">IRCompileLayer</span><span class="o"><</span><span class="n">decltype</span><span class="p">(</span><span class="n">ObjectLayer</span><span class="p">)</span><span class="o">></span> <span class="n">CompileLayer</span><span class="p">;</span>
+
+  <span class="k">typedef</span> <span class="n">std</span><span class="o">::</span><span class="n">function</span><span class="o"><</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span><span class="p">)</span><span class="o">></span>
+    <span class="n">OptimizeFunction</span><span class="p">;</span>
+
+  <span class="n">IRTransformLayer</span><span class="o"><</span><span class="n">decltype</span><span class="p">(</span><span class="n">CompileLayer</span><span class="p">),</span> <span class="n">OptimizeFunction</span><span class="o">></span> <span class="n">OptimizeLayer</span><span class="p">;</span>
+
+  <span class="n">JITCompileCallbackManager</span> <span class="o">*</span><span class="n">CompileCallbackMgr</span><span class="p">;</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">IndirectStubsManager</span><span class="o">></span> <span class="n">IndirectStubsMgr</span><span class="p">;</span>
+  <span class="n">MyRemote</span> <span class="o">&</span><span class="n">Remote</span><span class="p">;</span>
+
+<span class="nl">public:</span>
+  <span class="k">typedef</span> <span class="n">decltype</span><span class="p">(</span><span class="n">OptimizeLayer</span><span class="p">)</span><span class="o">::</span><span class="n">ModuleSetHandleT</span> <span class="n">ModuleHandle</span><span class="p">;</span>
+
+  <span class="n">KaleidoscopeJIT</span><span class="p">(</span><span class="n">MyRemote</span> <span class="o">&</span><span class="n">Remote</span><span class="p">)</span>
+      <span class="o">:</span> <span class="n">TM</span><span class="p">(</span><span class="n">EngineBuilder</span><span class="p">().</span><span class="n">selectTarget</span><span class="p">()),</span>
+        <span class="n">DL</span><span class="p">(</span><span class="n">TM</span><span class="o">-></span><span class="n">createDataLayout</span><span class="p">()),</span>
+        <span class="n">CompileLayer</span><span class="p">(</span><span class="n">ObjectLayer</span><span class="p">,</span> <span class="n">SimpleCompiler</span><span class="p">(</span><span class="o">*</span><span class="n">TM</span><span class="p">)),</span>
+        <span class="n">OptimizeLayer</span><span class="p">(</span><span class="n">CompileLayer</span><span class="p">,</span>
+                      <span class="p">[</span><span class="k">this</span><span class="p">](</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span> <span class="n">M</span><span class="p">)</span> <span class="p">{</span>
+                        <span class="k">return</span> <span class="n">optimizeModule</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">M</span><span class="p">));</span>
+                      <span class="p">}),</span>
+        <span class="n">Remote</span><span class="p">(</span><span class="n">Remote</span><span class="p">)</span> <span class="p">{</span>
+    <span class="k">auto</span> <span class="n">CCMgrOrErr</span> <span class="o">=</span> <span class="n">Remote</span><span class="p">.</span><span class="n">enableCompileCallbacks</span><span class="p">(</span><span class="mi">0</span><span class="p">);</span>
+    <span class="k">if</span> <span class="p">(</span><span class="o">!</span><span class="n">CCMgrOrErr</span><span class="p">)</span> <span class="p">{</span>
+      <span class="n">logAllUnhandledErrors</span><span class="p">(</span><span class="n">CCMgrOrErr</span><span class="p">.</span><span class="n">takeError</span><span class="p">(),</span> <span class="n">errs</span><span class="p">(),</span>
+                            <span class="s">"Error enabling remote compile callbacks:"</span><span class="p">);</span>
+      <span class="n">exit</span><span class="p">(</span><span class="mi">1</span><span class="p">);</span>
+    <span class="p">}</span>
+    <span class="n">CompileCallbackMgr</span> <span class="o">=</span> <span class="o">&*</span><span class="n">CCMgrOrErr</span><span class="p">;</span>
+    <span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">MyRemote</span><span class="o">::</span><span class="n">RCIndirectStubsManager</span><span class="o">></span> <span class="n">ISM</span><span class="p">;</span>
+    <span class="k">if</span> <span class="p">(</span><span class="k">auto</span> <span class="n">Err</span> <span class="o">=</span> <span class="n">Remote</span><span class="p">.</span><span class="n">createIndirectStubsManager</span><span class="p">(</span><span class="n">ISM</span><span class="p">))</span> <span class="p">{</span>
+      <span class="n">logAllUnhandledErrors</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Err</span><span class="p">),</span> <span class="n">errs</span><span class="p">(),</span>
+                            <span class="s">"Error creating indirect stubs manager:"</span><span class="p">);</span>
+      <span class="n">exit</span><span class="p">(</span><span class="mi">1</span><span class="p">);</span>
+    <span class="p">}</span>
+    <span class="n">IndirectStubsMgr</span> <span class="o">=</span> <span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">ISM</span><span class="p">);</span>
+    <span class="n">llvm</span><span class="o">::</span><span class="n">sys</span><span class="o">::</span><span class="n">DynamicLibrary</span><span class="o">::</span><span class="n">LoadLibraryPermanently</span><span class="p">(</span><span class="n">nullptr</span><span class="p">);</span>
+  <span class="p">}</span>
+
+  <span class="n">TargetMachine</span> <span class="o">&</span><span class="n">getTargetMachine</span><span class="p">()</span> <span class="p">{</span> <span class="k">return</span> <span class="o">*</span><span class="n">TM</span><span class="p">;</span> <span class="p">}</span>
+
+  <span class="n">ModuleHandle</span> <span class="n">addModule</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span> <span class="n">M</span><span class="p">)</span> <span class="p">{</span>
+
+    <span class="c1">// Build our symbol resolver:</span>
+    <span class="c1">// Lambda 1: Look back into the JIT itself to find symbols that are part of</span>
+    <span class="c1">//           the same "logical dylib".</span>
+    <span class="c1">// Lambda 2: Search for external symbols in the host process.</span>
+    <span class="k">auto</span> <span class="n">Resolver</span> <span class="o">=</span> <span class="n">createLambdaResolver</span><span class="p">(</span>
+        <span class="p">[</span><span class="o">&</span><span class="p">](</span><span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="o">&</span><span class="n">Name</span><span class="p">)</span> <span class="p">{</span>
+          <span class="k">if</span> <span class="p">(</span><span class="k">auto</span> <span class="n">Sym</span> <span class="o">=</span> <span class="n">IndirectStubsMgr</span><span class="o">-></span><span class="n">findStub</span><span class="p">(</span><span class="n">Name</span><span class="p">,</span> <span class="nb">false</span><span class="p">))</span>
+            <span class="k">return</span> <span class="n">Sym</span><span class="p">.</span><span class="n">toRuntimeDyldSymbol</span><span class="p">();</span>
+          <span class="k">if</span> <span class="p">(</span><span class="k">auto</span> <span class="n">Sym</span> <span class="o">=</span> <span class="n">OptimizeLayer</span><span class="p">.</span><span class="n">findSymbol</span><span class="p">(</span><span class="n">Name</span><span class="p">,</span> <span class="nb">false</span><span class="p">))</span>
+            <span class="k">return</span> <span class="n">Sym</span><span class="p">.</span><span class="n">toRuntimeDyldSymbol</span><span class="p">();</span>
+          <span class="k">return</span> <span class="n">RuntimeDyld</span><span class="o">::</span><span class="n">SymbolInfo</span><span class="p">(</span><span class="n">nullptr</span><span class="p">);</span>
+        <span class="p">},</span>
+        <span class="p">[</span><span class="o">&</span><span class="p">](</span><span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="o">&</span><span class="n">Name</span><span class="p">)</span> <span class="p">{</span>
+          <span class="k">if</span> <span class="p">(</span><span class="k">auto</span> <span class="n">AddrOrErr</span> <span class="o">=</span> <span class="n">Remote</span><span class="p">.</span><span class="n">getSymbolAddress</span><span class="p">(</span><span class="n">Name</span><span class="p">))</span>
+            <span class="k">return</span> <span class="n">RuntimeDyld</span><span class="o">::</span><span class="n">SymbolInfo</span><span class="p">(</span><span class="o">*</span><span class="n">AddrOrErr</span><span class="p">,</span>
+                                           <span class="n">JITSymbolFlags</span><span class="o">::</span><span class="n">Exported</span><span class="p">);</span>
+          <span class="k">else</span> <span class="p">{</span>
+            <span class="n">logAllUnhandledErrors</span><span class="p">(</span><span class="n">AddrOrErr</span><span class="p">.</span><span class="n">takeError</span><span class="p">(),</span> <span class="n">errs</span><span class="p">(),</span>
+                                  <span class="s">"Error resolving remote symbol:"</span><span class="p">);</span>
+            <span class="n">exit</span><span class="p">(</span><span class="mi">1</span><span class="p">);</span>
+          <span class="p">}</span>
+          <span class="k">return</span> <span class="n">RuntimeDyld</span><span class="o">::</span><span class="n">SymbolInfo</span><span class="p">(</span><span class="n">nullptr</span><span class="p">);</span>
+        <span class="p">});</span>
+
+    <span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">MyRemote</span><span class="o">::</span><span class="n">RCMemoryManager</span><span class="o">></span> <span class="n">MemMgr</span><span class="p">;</span>
+    <span class="k">if</span> <span class="p">(</span><span class="k">auto</span> <span class="n">Err</span> <span class="o">=</span> <span class="n">Remote</span><span class="p">.</span><span class="n">createRemoteMemoryManager</span><span class="p">(</span><span class="n">MemMgr</span><span class="p">))</span> <span class="p">{</span>
+      <span class="n">logAllUnhandledErrors</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Err</span><span class="p">),</span> <span class="n">errs</span><span class="p">(),</span>
+                            <span class="s">"Error creating remote memory manager:"</span><span class="p">);</span>
+      <span class="n">exit</span><span class="p">(</span><span class="mi">1</span><span class="p">);</span>
+    <span class="p">}</span>
+
+    <span class="c1">// Build a singlton module set to hold our module.</span>
+    <span class="n">std</span><span class="o">::</span><span class="n">vector</span><span class="o"><</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">>></span> <span class="n">Ms</span><span class="p">;</span>
+    <span class="n">Ms</span><span class="p">.</span><span class="n">push_back</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">M</span><span class="p">));</span>
+
+    <span class="c1">// Add the set to the JIT with the resolver we created above and a newly</span>
+    <span class="c1">// created SectionMemoryManager.</span>
+    <span class="k">return</span> <span class="n">OptimizeLayer</span><span class="p">.</span><span class="n">addModuleSet</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Ms</span><span class="p">),</span>
+                                      <span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">MemMgr</span><span class="p">),</span>
+                                      <span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Resolver</span><span class="p">));</span>
+  <span class="p">}</span>
+
+  <span class="n">Error</span> <span class="n">addFunctionAST</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">FunctionAST</span><span class="o">></span> <span class="n">FnAST</span><span class="p">)</span> <span class="p">{</span>
+    <span class="c1">// Create a CompileCallback - this is the re-entry point into the compiler</span>
+    <span class="c1">// for functions that haven't been compiled yet.</span>
+    <span class="k">auto</span> <span class="n">CCInfo</span> <span class="o">=</span> <span class="n">CompileCallbackMgr</span><span class="o">-></span><span class="n">getCompileCallback</span><span class="p">();</span>
+
+    <span class="c1">// Create an indirect stub. This serves as the functions "canonical</span>
+    <span class="c1">// definition" - an unchanging (constant address) entry point to the</span>
+    <span class="c1">// function implementation.</span>
+    <span class="c1">// Initially we point the stub's function-pointer at the compile callback</span>
+    <span class="c1">// that we just created. In the compile action for the callback (see below)</span>
+    <span class="c1">// we will update the stub's function pointer to point at the function</span>
+    <span class="c1">// implementation that we just implemented.</span>
+    <span class="k">if</span> <span class="p">(</span><span class="k">auto</span> <span class="n">Err</span> <span class="o">=</span> <span class="n">IndirectStubsMgr</span><span class="o">-></span><span class="n">createStub</span><span class="p">(</span><span class="n">mangle</span><span class="p">(</span><span class="n">FnAST</span><span class="o">-></span><span class="n">getName</span><span class="p">()),</span>
+                                                <span class="n">CCInfo</span><span class="p">.</span><span class="n">getAddress</span><span class="p">(),</span>
+                                                <span class="n">JITSymbolFlags</span><span class="o">::</span><span class="n">Exported</span><span class="p">))</span>
+      <span class="k">return</span> <span class="n">Err</span><span class="p">;</span>
+
+    <span class="c1">// Move ownership of FnAST to a shared pointer - C++11 lambdas don't support</span>
+    <span class="c1">// capture-by-move, which is be required for unique_ptr.</span>
+    <span class="k">auto</span> <span class="n">SharedFnAST</span> <span class="o">=</span> <span class="n">std</span><span class="o">::</span><span class="n">shared_ptr</span><span class="o"><</span><span class="n">FunctionAST</span><span class="o">></span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">FnAST</span><span class="p">));</span>
+
+    <span class="c1">// Set the action to compile our AST. This lambda will be run if/when</span>
+    <span class="c1">// execution hits the compile callback (via the stub).</span>
+    <span class="c1">//</span>
+    <span class="c1">// The steps to compile are:</span>
+    <span class="c1">// (1) IRGen the function.</span>
+    <span class="c1">// (2) Add the IR module to the JIT to make it executable like any other</span>
+    <span class="c1">//     module.</span>
+    <span class="c1">// (3) Use findSymbol to get the address of the compiled function.</span>
+    <span class="c1">// (4) Update the stub pointer to point at the implementation so that</span>
+    <span class="c1">///    subsequent calls go directly to it and bypass the compiler.</span>
+    <span class="c1">// (5) Return the address of the implementation: this lambda will actually</span>
+    <span class="c1">//     be run inside an attempted call to the function, and we need to</span>
+    <span class="c1">//     continue on to the implementation to complete the attempted call.</span>
+    <span class="c1">//     The JIT runtime (the resolver block) will use the return address of</span>
+    <span class="c1">//     this function as the address to continue at once it has reset the</span>
+    <span class="c1">//     CPU state to what it was immediately before the call.</span>
+    <span class="n">CCInfo</span><span class="p">.</span><span class="n">setCompileAction</span><span class="p">(</span>
+      <span class="p">[</span><span class="k">this</span><span class="p">,</span> <span class="n">SharedFnAST</span><span class="p">]()</span> <span class="p">{</span>
+        <span class="k">auto</span> <span class="n">M</span> <span class="o">=</span> <span class="n">irgenAndTakeOwnership</span><span class="p">(</span><span class="o">*</span><span class="n">SharedFnAST</span><span class="p">,</span> <span class="s">"$impl"</span><span class="p">);</span>
+        <span class="n">addModule</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">M</span><span class="p">));</span>
+        <span class="k">auto</span> <span class="n">Sym</span> <span class="o">=</span> <span class="n">findSymbol</span><span class="p">(</span><span class="n">SharedFnAST</span><span class="o">-></span><span class="n">getName</span><span class="p">()</span> <span class="o">+</span> <span class="s">"$impl"</span><span class="p">);</span>
+        <span class="n">assert</span><span class="p">(</span><span class="n">Sym</span> <span class="o">&&</span> <span class="s">"Couldn't find compiled function?"</span><span class="p">);</span>
+        <span class="n">TargetAddress</span> <span class="n">SymAddr</span> <span class="o">=</span> <span class="n">Sym</span><span class="p">.</span><span class="n">getAddress</span><span class="p">();</span>
+        <span class="k">if</span> <span class="p">(</span><span class="k">auto</span> <span class="n">Err</span> <span class="o">=</span>
+              <span class="n">IndirectStubsMgr</span><span class="o">-></span><span class="n">updatePointer</span><span class="p">(</span><span class="n">mangle</span><span class="p">(</span><span class="n">SharedFnAST</span><span class="o">-></span><span class="n">getName</span><span class="p">()),</span>
+                                              <span class="n">SymAddr</span><span class="p">))</span> <span class="p">{</span>
+          <span class="n">logAllUnhandledErrors</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">move</span><span class="p">(</span><span class="n">Err</span><span class="p">),</span> <span class="n">errs</span><span class="p">(),</span>
+                                <span class="s">"Error updating function pointer: "</span><span class="p">);</span>
+          <span class="n">exit</span><span class="p">(</span><span class="mi">1</span><span class="p">);</span>
+        <span class="p">}</span>
+
+        <span class="k">return</span> <span class="n">SymAddr</span><span class="p">;</span>
+      <span class="p">});</span>
+
+    <span class="k">return</span> <span class="n">Error</span><span class="o">::</span><span class="n">success</span><span class="p">();</span>
+  <span class="p">}</span>
+
+  <span class="n">Error</span> <span class="n">executeRemoteExpr</span><span class="p">(</span><span class="n">TargetAddress</span> <span class="n">ExprAddr</span><span class="p">)</span> <span class="p">{</span>
+    <span class="k">return</span> <span class="n">Remote</span><span class="p">.</span><span class="n">callVoidVoid</span><span class="p">(</span><span class="n">ExprAddr</span><span class="p">);</span>
+  <span class="p">}</span>
+
+  <span class="n">JITSymbol</span> <span class="n">findSymbol</span><span class="p">(</span><span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="n">Name</span><span class="p">)</span> <span class="p">{</span>
+    <span class="k">return</span> <span class="n">OptimizeLayer</span><span class="p">.</span><span class="n">findSymbol</span><span class="p">(</span><span class="n">mangle</span><span class="p">(</span><span class="n">Name</span><span class="p">),</span> <span class="nb">true</span><span class="p">);</span>
+  <span class="p">}</span>
+
+  <span class="kt">void</span> <span class="n">removeModule</span><span class="p">(</span><span class="n">ModuleHandle</span> <span class="n">H</span><span class="p">)</span> <span class="p">{</span>
+    <span class="n">OptimizeLayer</span><span class="p">.</span><span class="n">removeModuleSet</span><span class="p">(</span><span class="n">H</span><span class="p">);</span>
+  <span class="p">}</span>
+
+<span class="nl">private:</span>
+
+  <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="n">mangle</span><span class="p">(</span><span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="o">&</span><span class="n">Name</span><span class="p">)</span> <span class="p">{</span>
+    <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="n">MangledName</span><span class="p">;</span>
+    <span class="n">raw_string_ostream</span> <span class="nf">MangledNameStream</span><span class="p">(</span><span class="n">MangledName</span><span class="p">);</span>
+    <span class="n">Mangler</span><span class="o">::</span><span class="n">getNameWithPrefix</span><span class="p">(</span><span class="n">MangledNameStream</span><span class="p">,</span> <span class="n">Name</span><span class="p">,</span> <span class="n">DL</span><span class="p">);</span>
+    <span class="k">return</span> <span class="n">MangledNameStream</span><span class="p">.</span><span class="n">str</span><span class="p">();</span>
+  <span class="p">}</span>
+
+  <span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span> <span class="n">optimizeModule</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">unique_ptr</span><span class="o"><</span><span class="n">Module</span><span class="o">></span> <span class="n">M</span><span class="p">)</span> <span class="p">{</span>
+    <span class="c1">// Create a function pass manager.</span>
+    <span class="k">auto</span> <span class="n">FPM</span> <span class="o">=</span> <span class="n">llvm</span><span class="o">::</span><span class="n">make_unique</span><span class="o"><</span><span class="n">legacy</span><span class="o">::</span><span class="n">FunctionPassManager</span><span class="o">></span><span class="p">(</span><span class="n">M</span><span class="p">.</span><span class="n">get</span><span class="p">());</span>
+
+    <span class="c1">// Add some optimizations.</span>
+    <span class="n">FPM</span><span class="o">-></span><span class="n">add</span><span class="p">(</span><span class="n">createInstructionCombiningPass</span><span class="p">());</span>
+    <span class="n">FPM</span><span class="o">-></span><span class="n">add</span><span class="p">(</span><span class="n">createReassociatePass</span><span class="p">());</span>
+    <span class="n">FPM</span><span class="o">-></span><span class="n">add</span><span class="p">(</span><span class="n">createGVNPass</span><span class="p">());</span>
+    <span class="n">FPM</span><span class="o">-></span><span class="n">add</span><span class="p">(</span><span class="n">createCFGSimplificationPass</span><span class="p">());</span>
+    <span class="n">FPM</span><span class="o">-></span><span class="n">doInitialization</span><span class="p">();</span>
+
+    <span class="c1">// Run the optimizations over all functions in the module being added to</span>
+    <span class="c1">// the JIT.</span>
+    <span class="k">for</span> <span class="p">(</span><span class="k">auto</span> <span class="o">&</span><span class="n">F</span> <span class="o">:</span> <span class="o">*</span><span class="n">M</span><span class="p">)</span>
+      <span class="n">FPM</span><span class="o">-></span><span class="n">run</span><span class="p">(</span><span class="n">F</span><span class="p">);</span>
+
+    <span class="k">return</span> <span class="n">M</span><span class="p">;</span>
+  <span class="p">}</span>
+
+<span class="p">};</span>
+
+<span class="p">}</span> <span class="c1">// end namespace orc</span>
+<span class="p">}</span> <span class="c1">// end namespace llvm</span>
+
+<span class="cp">#endif </span><span class="c1">// LLVM_EXECUTIONENGINE_ORC_KALEIDOSCOPEJIT_H</span>
+</pre></div>
+</div>
+<p>And the code for the JIT server:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="cp">#include "llvm/Support/CommandLine.h"</span>
+<span class="cp">#include "llvm/Support/DynamicLibrary.h"</span>
+<span class="cp">#include "llvm/Support/TargetSelect.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/OrcRemoteTargetServer.h"</span>
+<span class="cp">#include "llvm/ExecutionEngine/Orc/OrcABISupport.h"</span>
+
+<span class="cp">#include "../RemoteJITUtils.h"</span>
+
+<span class="cp">#include <cstring></span>
+<span class="cp">#include <unistd.h></span>
+<span class="cp">#include <netinet/in.h></span>
+<span class="cp">#include <sys/socket.h></span>
+
+
+<span class="k">using</span> <span class="k">namespace</span> <span class="n">llvm</span><span class="p">;</span>
+<span class="k">using</span> <span class="k">namespace</span> <span class="n">llvm</span><span class="o">::</span><span class="n">orc</span><span class="p">;</span>
+
+<span class="c1">// Command line argument for TCP port.</span>
+<span class="n">cl</span><span class="o">::</span><span class="n">opt</span><span class="o"><</span><span class="kt">uint32_t</span><span class="o">></span> <span class="n">Port</span><span class="p">(</span><span class="s">"port"</span><span class="p">,</span>
+                       <span class="n">cl</span><span class="o">::</span><span class="n">desc</span><span class="p">(</span><span class="s">"TCP port to listen on"</span><span class="p">),</span>
+                       <span class="n">cl</span><span class="o">::</span><span class="n">init</span><span class="p">(</span><span class="mi">20000</span><span class="p">));</span>
+
+<span class="n">ExitOnError</span> <span class="n">ExitOnErr</span><span class="p">;</span>
+
+<span class="k">typedef</span> <span class="nf">int</span> <span class="p">(</span><span class="o">*</span><span class="n">MainFun</span><span class="p">)(</span><span class="kt">int</span><span class="p">,</span> <span class="k">const</span> <span class="kt">char</span><span class="o">*</span><span class="p">[]);</span>
+
+<span class="k">template</span> <span class="o"><</span><span class="k">typename</span> <span class="n">NativePtrT</span><span class="o">></span>
+<span class="n">NativePtrT</span> <span class="n">MakeNative</span><span class="p">(</span><span class="kt">uint64_t</span> <span class="n">P</span><span class="p">)</span> <span class="p">{</span>
+  <span class="k">return</span> <span class="k">reinterpret_cast</span><span class="o"><</span><span class="n">NativePtrT</span><span class="o">></span><span class="p">(</span><span class="k">static_cast</span><span class="o"><</span><span class="kt">uintptr_t</span><span class="o">></span><span class="p">(</span><span class="n">P</span><span class="p">));</span>
+<span class="p">}</span>
+
+<span class="k">extern</span> <span class="s">"C"</span>
+<span class="kt">void</span> <span class="n">printExprResult</span><span class="p">(</span><span class="kt">double</span> <span class="n">Val</span><span class="p">)</span> <span class="p">{</span>
+  <span class="n">printf</span><span class="p">(</span><span class="s">"Expression evaluated to: %f</span><span class="se">\n</span><span class="s">"</span><span class="p">,</span> <span class="n">Val</span><span class="p">);</span>
+<span class="p">}</span>
+
+<span class="c1">// --- LAZY COMPILE TEST ---</span>
+<span class="kt">int</span> <span class="n">main</span><span class="p">(</span><span class="kt">int</span> <span class="n">argc</span><span class="p">,</span> <span class="kt">char</span><span class="o">*</span> <span class="n">argv</span><span class="p">[])</span> <span class="p">{</span>
+
+  <span class="k">if</span> <span class="p">(</span><span class="n">argc</span> <span class="o">==</span> <span class="mi">0</span><span class="p">)</span>
+    <span class="n">ExitOnErr</span><span class="p">.</span><span class="n">setBanner</span><span class="p">(</span><span class="s">"jit_server: "</span><span class="p">);</span>
+  <span class="k">else</span>
+    <span class="n">ExitOnErr</span><span class="p">.</span><span class="n">setBanner</span><span class="p">(</span><span class="n">std</span><span class="o">::</span><span class="n">string</span><span class="p">(</span><span class="n">argv</span><span class="p">[</span><span class="mi">0</span><span class="p">])</span> <span class="o">+</span> <span class="s">": "</span><span class="p">);</span>
+
+  <span class="c1">// --- Initialize LLVM ---</span>
+  <span class="n">cl</span><span class="o">::</span><span class="n">ParseCommandLineOptions</span><span class="p">(</span><span class="n">argc</span><span class="p">,</span> <span class="n">argv</span><span class="p">,</span> <span class="s">"LLVM lazy JIT example.</span><span class="se">\n</span><span class="s">"</span><span class="p">);</span>
+
+  <span class="n">InitializeNativeTarget</span><span class="p">();</span>
+  <span class="n">InitializeNativeTargetAsmPrinter</span><span class="p">();</span>
+  <span class="n">InitializeNativeTargetAsmParser</span><span class="p">();</span>
+
+  <span class="k">if</span> <span class="p">(</span><span class="n">sys</span><span class="o">::</span><span class="n">DynamicLibrary</span><span class="o">::</span><span class="n">LoadLibraryPermanently</span><span class="p">(</span><span class="n">nullptr</span><span class="p">))</span> <span class="p">{</span>
+    <span class="n">errs</span><span class="p">()</span> <span class="o"><<</span> <span class="s">"Error loading program symbols.</span><span class="se">\n</span><span class="s">"</span><span class="p">;</span>
+    <span class="k">return</span> <span class="mi">1</span><span class="p">;</span>
+  <span class="p">}</span>
+
+  <span class="c1">// --- Initialize remote connection ---</span>
+
+  <span class="kt">int</span> <span class="n">sockfd</span> <span class="o">=</span> <span class="n">socket</span><span class="p">(</span><span class="n">PF_INET</span><span class="p">,</span> <span class="n">SOCK_STREAM</span><span class="p">,</span> <span class="mi">0</span><span class="p">);</span>
+  <span class="n">sockaddr_in</span> <span class="n">servAddr</span><span class="p">,</span> <span class="n">clientAddr</span><span class="p">;</span>
+  <span class="kt">socklen_t</span> <span class="n">clientAddrLen</span> <span class="o">=</span> <span class="k">sizeof</span><span class="p">(</span><span class="n">clientAddr</span><span class="p">);</span>
+  <span class="n">bzero</span><span class="p">(</span><span class="o">&</span><span class="n">servAddr</span><span class="p">,</span> <span class="k">sizeof</span><span class="p">(</span><span class="n">servAddr</span><span class="p">));</span>
+  <span class="n">servAddr</span><span class="p">.</span><span class="n">sin_family</span> <span class="o">=</span> <span class="n">PF_INET</span><span class="p">;</span>
+  <span class="n">servAddr</span><span class="p">.</span><span class="n">sin_family</span> <span class="o">=</span> <span class="n">INADDR_ANY</span><span class="p">;</span>
+  <span class="n">servAddr</span><span class="p">.</span><span class="n">sin_port</span> <span class="o">=</span> <span class="n">htons</span><span class="p">(</span><span class="n">Port</span><span class="p">);</span>
+
+  <span class="p">{</span>
+    <span class="c1">// avoid "Address already in use" error.</span>
+    <span class="kt">int</span> <span class="n">yes</span><span class="o">=</span><span class="mi">1</span><span class="p">;</span>
+    <span class="k">if</span> <span class="p">(</span><span class="n">setsockopt</span><span class="p">(</span><span class="n">sockfd</span><span class="p">,</span><span class="n">SOL_SOCKET</span><span class="p">,</span><span class="n">SO_REUSEADDR</span><span class="p">,</span><span class="o">&</span><span class="n">yes</span><span class="p">,</span><span class="k">sizeof</span><span class="p">(</span><span class="kt">int</span><span class="p">))</span> <span class="o">==</span> <span class="o">-</span><span class="mi">1</span><span class="p">)</span> <span class="p">{</span>
+      <span class="n">errs</span><span class="p">()</span> <span class="o"><<</span> <span class="s">"Error calling setsockopt.</span><span class="se">\n</span><span class="s">"</span><span class="p">;</span>
+      <span class="k">return</span> <span class="mi">1</span><span class="p">;</span>
+    <span class="p">}</span>
+  <span class="p">}</span>
+
+  <span class="k">if</span> <span class="p">(</span><span class="n">bind</span><span class="p">(</span><span class="n">sockfd</span><span class="p">,</span> <span class="k">reinterpret_cast</span><span class="o"><</span><span class="n">sockaddr</span><span class="o">*></span><span class="p">(</span><span class="o">&</span><span class="n">servAddr</span><span class="p">),</span>
+           <span class="k">sizeof</span><span class="p">(</span><span class="n">servAddr</span><span class="p">))</span> <span class="o"><</span> <span class="mi">0</span><span class="p">)</span> <span class="p">{</span>
+    <span class="n">errs</span><span class="p">()</span> <span class="o"><<</span> <span class="s">"Error on binding.</span><span class="se">\n</span><span class="s">"</span><span class="p">;</span>
+    <span class="k">return</span> <span class="mi">1</span><span class="p">;</span>
+  <span class="p">}</span>
+  <span class="n">listen</span><span class="p">(</span><span class="n">sockfd</span><span class="p">,</span> <span class="mi">1</span><span class="p">);</span>
+  <span class="kt">int</span> <span class="n">newsockfd</span> <span class="o">=</span> <span class="n">accept</span><span class="p">(</span><span class="n">sockfd</span><span class="p">,</span> <span class="k">reinterpret_cast</span><span class="o"><</span><span class="n">sockaddr</span><span class="o">*></span><span class="p">(</span><span class="o">&</span><span class="n">clientAddr</span><span class="p">),</span>
+                         <span class="o">&</span><span class="n">clientAddrLen</span><span class="p">);</span>
+
+  <span class="k">auto</span> <span class="n">SymbolLookup</span> <span class="o">=</span>
+    <span class="p">[](</span><span class="k">const</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="o">&</span><span class="n">Name</span><span class="p">)</span> <span class="p">{</span>
+      <span class="k">return</span> <span class="n">RTDyldMemoryManager</span><span class="o">::</span><span class="n">getSymbolAddressInProcess</span><span class="p">(</span><span class="n">Name</span><span class="p">);</span>
+    <span class="p">};</span>
+
+  <span class="k">auto</span> <span class="n">RegisterEHFrames</span> <span class="o">=</span>
+    <span class="p">[](</span><span class="kt">uint8_t</span> <span class="o">*</span><span class="n">Addr</span><span class="p">,</span> <span class="kt">uint32_t</span> <span class="n">Size</span><span class="p">)</span> <span class="p">{</span>
+      <span class="n">RTDyldMemoryManager</span><span class="o">::</span><span class="n">registerEHFramesInProcess</span><span class="p">(</span><span class="n">Addr</span><span class="p">,</span> <span class="n">Size</span><span class="p">);</span>
+    <span class="p">};</span>
+
+  <span class="k">auto</span> <span class="n">DeregisterEHFrames</span> <span class="o">=</span>
+    <span class="p">[](</span><span class="kt">uint8_t</span> <span class="o">*</span><span class="n">Addr</span><span class="p">,</span> <span class="kt">uint32_t</span> <span class="n">Size</span><span class="p">)</span> <span class="p">{</span>
+      <span class="n">RTDyldMemoryManager</span><span class="o">::</span><span class="n">deregisterEHFramesInProcess</span><span class="p">(</span><span class="n">Addr</span><span class="p">,</span> <span class="n">Size</span><span class="p">);</span>
+    <span class="p">};</span>
+
+  <span class="n">FDRPCChannel</span> <span class="nf">TCPChannel</span><span class="p">(</span><span class="n">newsockfd</span><span class="p">,</span> <span class="n">newsockfd</span><span class="p">);</span>
+  <span class="k">typedef</span> <span class="n">remote</span><span class="o">::</span><span class="n">OrcRemoteTargetServer</span><span class="o"><</span><span class="n">FDRPCChannel</span><span class="p">,</span> <span class="n">OrcX86_64_SysV</span><span class="o">></span> <span class="n">MyServerT</span><span class="p">;</span>
+
+  <span class="n">MyServerT</span> <span class="nf">Server</span><span class="p">(</span><span class="n">TCPChannel</span><span class="p">,</span> <span class="n">SymbolLookup</span><span class="p">,</span> <span class="n">RegisterEHFrames</span><span class="p">,</span> <span class="n">DeregisterEHFrames</span><span class="p">);</span>
+
+  <span class="k">while</span> <span class="p">(</span><span class="mi">1</span><span class="p">)</span> <span class="p">{</span>
+    <span class="n">MyServerT</span><span class="o">::</span><span class="n">JITFuncId</span> <span class="n">Id</span> <span class="o">=</span> <span class="n">MyServerT</span><span class="o">::</span><span class="n">InvalidId</span><span class="p">;</span>
+    <span class="n">ExitOnErr</span><span class="p">(</span><span class="n">Server</span><span class="p">.</span><span class="n">startReceivingFunction</span><span class="p">(</span><span class="n">TCPChannel</span><span class="p">,</span> <span class="p">(</span><span class="kt">uint32_t</span><span class="o">&</span><span class="p">)</span><span class="n">Id</span><span class="p">));</span>
+    <span class="k">switch</span> <span class="p">(</span><span class="n">Id</span><span class="p">)</span> <span class="p">{</span>
+    <span class="k">case</span> <span class="n">MyServerT</span>:<span class="o">:</span><span class="n">TerminateSessionId</span><span class="o">:</span>
+      <span class="n">ExitOnErr</span><span class="p">(</span><span class="n">Server</span><span class="p">.</span><span class="n">handleTerminateSession</span><span class="p">());</span>
+      <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+    <span class="nl">default:</span>
+      <span class="n">ExitOnErr</span><span class="p">(</span><span class="n">Server</span><span class="p">.</span><span class="n">handleKnownFunction</span><span class="p">(</span><span class="n">Id</span><span class="p">));</span>
+      <span class="k">break</span><span class="p">;</span>
+    <span class="p">}</span>
+  <span class="p">}</span>
+
+  <span class="n">llvm_unreachable</span><span class="p">(</span><span class="s">"Fell through server command loop."</span><span class="p">);</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+</div>
+</div>
+
+
+          </div>
+      </div>
+      <div class="clearer"></div>
+    </div>
+    <div class="related">
+      <h3>Navigation</h3>
+      <ul>
+        <li class="right" style="margin-right: 10px">
+          <a href="../genindex.html" title="General Index"
+             >index</a></li>
+        <li class="right" >
+          <a href="../ReleaseNotes.html" title="LLVM 3.9 Release Notes"
+             >next</a> |</li>
+        <li class="right" >
+          <a href="BuildingAJIT4.html" title="4. Building a JIT: Extreme Laziness - Using Compile Callbacks to JIT from ASTs"
+             >previous</a> |</li>
+  <li><a href="http://llvm.org/">LLVM Home</a> | </li>
+  <li><a href="../index.html">Documentation</a>»</li>
+
+          <li><a href="index.html" >LLVM Tutorial: Table of Contents</a> »</li> 
+      </ul>
+    </div>
+    <div class="footer">
+        © Copyright 2003-2016, LLVM Project.
+      Last updated on 2016-12-21.
+      Created using <a href="http://sphinx-doc.org/">Sphinx</a> 1.2.2.
+    </div>
+  </body>
+</html>
\ No newline at end of file

Added: www-releases/trunk/3.9.1/docs/tutorial/LangImpl01.html
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.9.1/docs/tutorial/LangImpl01.html?rev=290368&view=auto
==============================================================================
--- www-releases/trunk/3.9.1/docs/tutorial/LangImpl01.html (added)
+++ www-releases/trunk/3.9.1/docs/tutorial/LangImpl01.html Thu Dec 22 14:04:03 2016
@@ -0,0 +1,366 @@
+
+<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN"
+  "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd">
+
+
+<html xmlns="http://www.w3.org/1999/xhtml">
+  <head>
+    <meta http-equiv="Content-Type" content="text/html; charset=utf-8" />
+    
+    <title>1. Kaleidoscope: Tutorial Introduction and the Lexer — LLVM 3.9 documentation</title>
+    
+    <link rel="stylesheet" href="../_static/llvm-theme.css" type="text/css" />
+    <link rel="stylesheet" href="../_static/pygments.css" type="text/css" />
+    
+    <script type="text/javascript">
+      var DOCUMENTATION_OPTIONS = {
+        URL_ROOT:    '../',
+        VERSION:     '3.9',
+        COLLAPSE_INDEX: false,
+        FILE_SUFFIX: '.html',
+        HAS_SOURCE:  true
+      };
+    </script>
+    <script type="text/javascript" src="../_static/jquery.js"></script>
+    <script type="text/javascript" src="../_static/underscore.js"></script>
+    <script type="text/javascript" src="../_static/doctools.js"></script>
+    <link rel="top" title="LLVM 3.9 documentation" href="../index.html" />
+    <link rel="up" title="LLVM Tutorial: Table of Contents" href="index.html" />
+    <link rel="next" title="2. Kaleidoscope: Implementing a Parser and AST" href="LangImpl02.html" />
+    <link rel="prev" title="LLVM Tutorial: Table of Contents" href="index.html" />
+<style type="text/css">
+  table.right { float: right; margin-left: 20px; }
+  table.right td { border: 1px solid #ccc; }
+</style>
+
+  </head>
+  <body>
+<div class="logo">
+  <a href="../index.html">
+    <img src="../_static/logo.png"
+         alt="LLVM Logo" width="250" height="88"/></a>
+</div>
+
+    <div class="related">
+      <h3>Navigation</h3>
+      <ul>
+        <li class="right" style="margin-right: 10px">
+          <a href="../genindex.html" title="General Index"
+             accesskey="I">index</a></li>
+        <li class="right" >
+          <a href="LangImpl02.html" title="2. Kaleidoscope: Implementing a Parser and AST"
+             accesskey="N">next</a> |</li>
+        <li class="right" >
+          <a href="index.html" title="LLVM Tutorial: Table of Contents"
+             accesskey="P">previous</a> |</li>
+  <li><a href="http://llvm.org/">LLVM Home</a> | </li>
+  <li><a href="../index.html">Documentation</a>»</li>
+
+          <li><a href="index.html" accesskey="U">LLVM Tutorial: Table of Contents</a> »</li> 
+      </ul>
+    </div>
+
+
+    <div class="document">
+      <div class="documentwrapper">
+          <div class="body">
+            
+  <div class="section" id="kaleidoscope-tutorial-introduction-and-the-lexer">
+<h1>1. Kaleidoscope: Tutorial Introduction and the Lexer<a class="headerlink" href="#kaleidoscope-tutorial-introduction-and-the-lexer" title="Permalink to this headline">¶</a></h1>
+<div class="contents local topic" id="contents">
+<ul class="simple">
+<li><a class="reference internal" href="#tutorial-introduction" id="id1">Tutorial Introduction</a></li>
+<li><a class="reference internal" href="#the-basic-language" id="id2">The Basic Language</a></li>
+<li><a class="reference internal" href="#the-lexer" id="id3">The Lexer</a></li>
+</ul>
+</div>
+<div class="section" id="tutorial-introduction">
+<h2><a class="toc-backref" href="#id1">1.1. Tutorial Introduction</a><a class="headerlink" href="#tutorial-introduction" title="Permalink to this headline">¶</a></h2>
+<p>Welcome to the “Implementing a language with LLVM” tutorial. This
+tutorial runs through the implementation of a simple language, showing
+how fun and easy it can be. This tutorial will get you up and started as
+well as help to build a framework you can extend to other languages. The
+code in this tutorial can also be used as a playground to hack on other
+LLVM specific things.</p>
+<p>The goal of this tutorial is to progressively unveil our language,
+describing how it is built up over time. This will let us cover a fairly
+broad range of language design and LLVM-specific usage issues, showing
+and explaining the code for it all along the way, without overwhelming
+you with tons of details up front.</p>
+<p>It is useful to point out ahead of time that this tutorial is really
+about teaching compiler techniques and LLVM specifically, <em>not</em> about
+teaching modern and sane software engineering principles. In practice,
+this means that we’ll take a number of shortcuts to simplify the
+exposition. For example, the code uses global variables
+all over the place, doesn’t use nice design patterns like
+<a class="reference external" href="http://en.wikipedia.org/wiki/Visitor_pattern">visitors</a>, etc... but
+it is very simple. If you dig in and use the code as a basis for future
+projects, fixing these deficiencies shouldn’t be hard.</p>
+<p>I’ve tried to put this tutorial together in a way that makes chapters
+easy to skip over if you are already familiar with or are uninterested
+in the various pieces. The structure of the tutorial is:</p>
+<ul class="simple">
+<li><a class="reference external" href="#language">Chapter #1</a>: Introduction to the Kaleidoscope
+language, and the definition of its Lexer - This shows where we are
+going and the basic functionality that we want it to do. In order to
+make this tutorial maximally understandable and hackable, we choose
+to implement everything in C++ instead of using lexer and parser
+generators. LLVM obviously works just fine with such tools, feel free
+to use one if you prefer.</li>
+<li><a class="reference external" href="LangImpl02.html">Chapter #2</a>: Implementing a Parser and AST -
+With the lexer in place, we can talk about parsing techniques and
+basic AST construction. This tutorial describes recursive descent
+parsing and operator precedence parsing. Nothing in Chapters 1 or 2
+is LLVM-specific, the code doesn’t even link in LLVM at this point.
+:)</li>
+<li><a class="reference external" href="LangImpl03.html">Chapter #3</a>: Code generation to LLVM IR - With
+the AST ready, we can show off how easy generation of LLVM IR really
+is.</li>
+<li><a class="reference external" href="LangImpl04.html">Chapter #4</a>: Adding JIT and Optimizer Support
+- Because a lot of people are interested in using LLVM as a JIT,
+we’ll dive right into it and show you the 3 lines it takes to add JIT
+support. LLVM is also useful in many other ways, but this is one
+simple and “sexy” way to show off its power. :)</li>
+<li><a class="reference external" href="LangImpl05.html">Chapter #5</a>: Extending the Language: Control
+Flow - With the language up and running, we show how to extend it
+with control flow operations (if/then/else and a ‘for’ loop). This
+gives us a chance to talk about simple SSA construction and control
+flow.</li>
+<li><a class="reference external" href="LangImpl06.html">Chapter #6</a>: Extending the Language:
+User-defined Operators - This is a silly but fun chapter that talks
+about extending the language to let the user program define their own
+arbitrary unary and binary operators (with assignable precedence!).
+This lets us build a significant piece of the “language” as library
+routines.</li>
+<li><a class="reference external" href="LangImpl07.html">Chapter #7</a>: Extending the Language: Mutable
+Variables - This chapter talks about adding user-defined local
+variables along with an assignment operator. The interesting part
+about this is how easy and trivial it is to construct SSA form in
+LLVM: no, LLVM does <em>not</em> require your front-end to construct SSA
+form!</li>
+<li><a class="reference external" href="LangImpl08.html">Chapter #8</a>: Compiling to Object Files - This
+chapter explains how to take LLVM IR and compile it down to object
+files.</li>
+<li><a class="reference external" href="LangImpl09.html">Chapter #9</a>: Extending the Language: Debug
+Information - Having built a decent little programming language with
+control flow, functions and mutable variables, we consider what it
+takes to add debug information to standalone executables. This debug
+information will allow you to set breakpoints in Kaleidoscope
+functions, print out argument variables, and call functions - all
+from within the debugger!</li>
+<li><a class="reference external" href="LangImpl10.html">Chapter #10</a>: Conclusion and other useful LLVM
+tidbits - This chapter wraps up the series by talking about
+potential ways to extend the language, but also includes a bunch of
+pointers to info about “special topics” like adding garbage
+collection support, exceptions, debugging, support for “spaghetti
+stacks”, and a bunch of other tips and tricks.</li>
+</ul>
+<p>By the end of the tutorial, we’ll have written a bit less than 1000 lines
+of non-comment, non-blank, lines of code. With this small amount of
+code, we’ll have built up a very reasonable compiler for a non-trivial
+language including a hand-written lexer, parser, AST, as well as code
+generation support with a JIT compiler. While other systems may have
+interesting “hello world” tutorials, I think the breadth of this
+tutorial is a great testament to the strengths of LLVM and why you
+should consider it if you’re interested in language or compiler design.</p>
+<p>A note about this tutorial: we expect you to extend the language and
+play with it on your own. Take the code and go crazy hacking away at it,
+compilers don’t need to be scary creatures - it can be a lot of fun to
+play with languages!</p>
+</div>
+<div class="section" id="the-basic-language">
+<h2><a class="toc-backref" href="#id2">1.2. The Basic Language</a><a class="headerlink" href="#the-basic-language" title="Permalink to this headline">¶</a></h2>
+<p>This tutorial will be illustrated with a toy language that we’ll call
+“<a class="reference external" href="http://en.wikipedia.org/wiki/Kaleidoscope">Kaleidoscope</a>” (derived
+from “meaning beautiful, form, and view”). Kaleidoscope is a procedural
+language that allows you to define functions, use conditionals, math,
+etc. Over the course of the tutorial, we’ll extend Kaleidoscope to
+support the if/then/else construct, a for loop, user defined operators,
+JIT compilation with a simple command line interface, etc.</p>
+<p>Because we want to keep things simple, the only datatype in Kaleidoscope
+is a 64-bit floating point type (aka ‘double’ in C parlance). As such,
+all values are implicitly double precision and the language doesn’t
+require type declarations. This gives the language a very nice and
+simple syntax. For example, the following simple example computes
+<a class="reference external" href="http://en.wikipedia.org/wiki/Fibonacci_number">Fibonacci numbers:</a></p>
+<div class="highlight-python"><div class="highlight"><pre># Compute the x'th fibonacci number.
+def fib(x)
+  if x < 3 then
+    1
+  else
+    fib(x-1)+fib(x-2)
+
+# This expression will compute the 40th number.
+fib(40)
+</pre></div>
+</div>
+<p>We also allow Kaleidoscope to call into standard library functions (the
+LLVM JIT makes this completely trivial). This means that you can use the
+‘extern’ keyword to define a function before you use it (this is also
+useful for mutually recursive functions). For example:</p>
+<div class="highlight-python"><div class="highlight"><pre>extern sin(arg);
+extern cos(arg);
+extern atan2(arg1 arg2);
+
+atan2(sin(.4), cos(42))
+</pre></div>
+</div>
+<p>A more interesting example is included in Chapter 6 where we write a
+little Kaleidoscope application that <a class="reference external" href="LangImpl06.html#kicking-the-tires">displays a Mandelbrot
+Set</a> at various levels of magnification.</p>
+<p>Lets dive into the implementation of this language!</p>
+</div>
+<div class="section" id="the-lexer">
+<h2><a class="toc-backref" href="#id3">1.3. The Lexer</a><a class="headerlink" href="#the-lexer" title="Permalink to this headline">¶</a></h2>
+<p>When it comes to implementing a language, the first thing needed is the
+ability to process a text file and recognize what it says. The
+traditional way to do this is to use a
+“<a class="reference external" href="http://en.wikipedia.org/wiki/Lexical_analysis">lexer</a>” (aka
+‘scanner’) to break the input up into “tokens”. Each token returned by
+the lexer includes a token code and potentially some metadata (e.g. the
+numeric value of a number). First, we define the possibilities:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">// The lexer returns tokens [0-255] if it is an unknown character, otherwise one</span>
+<span class="c1">// of these for known things.</span>
+<span class="k">enum</span> <span class="n">Token</span> <span class="p">{</span>
+  <span class="n">tok_eof</span> <span class="o">=</span> <span class="o">-</span><span class="mi">1</span><span class="p">,</span>
+
+  <span class="c1">// commands</span>
+  <span class="n">tok_def</span> <span class="o">=</span> <span class="o">-</span><span class="mi">2</span><span class="p">,</span>
+  <span class="n">tok_extern</span> <span class="o">=</span> <span class="o">-</span><span class="mi">3</span><span class="p">,</span>
+
+  <span class="c1">// primary</span>
+  <span class="n">tok_identifier</span> <span class="o">=</span> <span class="o">-</span><span class="mi">4</span><span class="p">,</span>
+  <span class="n">tok_number</span> <span class="o">=</span> <span class="o">-</span><span class="mi">5</span><span class="p">,</span>
+<span class="p">};</span>
+
+<span class="k">static</span> <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="n">IdentifierStr</span><span class="p">;</span> <span class="c1">// Filled in if tok_identifier</span>
+<span class="k">static</span> <span class="kt">double</span> <span class="n">NumVal</span><span class="p">;</span>             <span class="c1">// Filled in if tok_number</span>
+</pre></div>
+</div>
+<p>Each token returned by our lexer will either be one of the Token enum
+values or it will be an ‘unknown’ character like ‘+’, which is returned
+as its ASCII value. If the current token is an identifier, the
+<tt class="docutils literal"><span class="pre">IdentifierStr</span></tt> global variable holds the name of the identifier. If
+the current token is a numeric literal (like 1.0), <tt class="docutils literal"><span class="pre">NumVal</span></tt> holds its
+value. Note that we use global variables for simplicity, this is not the
+best choice for a real language implementation :).</p>
+<p>The actual implementation of the lexer is a single function named
+<tt class="docutils literal"><span class="pre">gettok</span></tt>. The <tt class="docutils literal"><span class="pre">gettok</span></tt> function is called to return the next token
+from standard input. Its definition starts as:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">/// gettok - Return the next token from standard input.</span>
+<span class="k">static</span> <span class="kt">int</span> <span class="nf">gettok</span><span class="p">()</span> <span class="p">{</span>
+  <span class="k">static</span> <span class="kt">int</span> <span class="n">LastChar</span> <span class="o">=</span> <span class="sc">' '</span><span class="p">;</span>
+
+  <span class="c1">// Skip any whitespace.</span>
+  <span class="k">while</span> <span class="p">(</span><span class="n">isspace</span><span class="p">(</span><span class="n">LastChar</span><span class="p">))</span>
+    <span class="n">LastChar</span> <span class="o">=</span> <span class="n">getchar</span><span class="p">();</span>
+</pre></div>
+</div>
+<p><tt class="docutils literal"><span class="pre">gettok</span></tt> works by calling the C <tt class="docutils literal"><span class="pre">getchar()</span></tt> function to read
+characters one at a time from standard input. It eats them as it
+recognizes them and stores the last character read, but not processed,
+in LastChar. The first thing that it has to do is ignore whitespace
+between tokens. This is accomplished with the loop above.</p>
+<p>The next thing <tt class="docutils literal"><span class="pre">gettok</span></tt> needs to do is recognize identifiers and
+specific keywords like “def”. Kaleidoscope does this with this simple
+loop:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="k">if</span> <span class="p">(</span><span class="n">isalpha</span><span class="p">(</span><span class="n">LastChar</span><span class="p">))</span> <span class="p">{</span> <span class="c1">// identifier: [a-zA-Z][a-zA-Z0-9]*</span>
+  <span class="n">IdentifierStr</span> <span class="o">=</span> <span class="n">LastChar</span><span class="p">;</span>
+  <span class="k">while</span> <span class="p">(</span><span class="n">isalnum</span><span class="p">((</span><span class="n">LastChar</span> <span class="o">=</span> <span class="n">getchar</span><span class="p">())))</span>
+    <span class="n">IdentifierStr</span> <span class="o">+=</span> <span class="n">LastChar</span><span class="p">;</span>
+
+  <span class="k">if</span> <span class="p">(</span><span class="n">IdentifierStr</span> <span class="o">==</span> <span class="s">"def"</span><span class="p">)</span>
+    <span class="k">return</span> <span class="n">tok_def</span><span class="p">;</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">IdentifierStr</span> <span class="o">==</span> <span class="s">"extern"</span><span class="p">)</span>
+    <span class="k">return</span> <span class="n">tok_extern</span><span class="p">;</span>
+  <span class="k">return</span> <span class="n">tok_identifier</span><span class="p">;</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>Note that this code sets the ‘<tt class="docutils literal"><span class="pre">IdentifierStr</span></tt>‘ global whenever it
+lexes an identifier. Also, since language keywords are matched by the
+same loop, we handle them here inline. Numeric values are similar:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="k">if</span> <span class="p">(</span><span class="n">isdigit</span><span class="p">(</span><span class="n">LastChar</span><span class="p">)</span> <span class="o">||</span> <span class="n">LastChar</span> <span class="o">==</span> <span class="sc">'.'</span><span class="p">)</span> <span class="p">{</span>   <span class="c1">// Number: [0-9.]+</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="n">NumStr</span><span class="p">;</span>
+  <span class="k">do</span> <span class="p">{</span>
+    <span class="n">NumStr</span> <span class="o">+=</span> <span class="n">LastChar</span><span class="p">;</span>
+    <span class="n">LastChar</span> <span class="o">=</span> <span class="n">getchar</span><span class="p">();</span>
+  <span class="p">}</span> <span class="k">while</span> <span class="p">(</span><span class="n">isdigit</span><span class="p">(</span><span class="n">LastChar</span><span class="p">)</span> <span class="o">||</span> <span class="n">LastChar</span> <span class="o">==</span> <span class="sc">'.'</span><span class="p">);</span>
+
+  <span class="n">NumVal</span> <span class="o">=</span> <span class="n">strtod</span><span class="p">(</span><span class="n">NumStr</span><span class="p">.</span><span class="n">c_str</span><span class="p">(),</span> <span class="mi">0</span><span class="p">);</span>
+  <span class="k">return</span> <span class="n">tok_number</span><span class="p">;</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>This is all pretty straight-forward code for processing input. When
+reading a numeric value from input, we use the C <tt class="docutils literal"><span class="pre">strtod</span></tt> function to
+convert it to a numeric value that we store in <tt class="docutils literal"><span class="pre">NumVal</span></tt>. Note that
+this isn’t doing sufficient error checking: it will incorrectly read
+“1.23.45.67” and handle it as if you typed in “1.23”. Feel free to
+extend it :). Next we handle comments:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="k">if</span> <span class="p">(</span><span class="n">LastChar</span> <span class="o">==</span> <span class="sc">'#'</span><span class="p">)</span> <span class="p">{</span>
+  <span class="c1">// Comment until end of line.</span>
+  <span class="k">do</span>
+    <span class="n">LastChar</span> <span class="o">=</span> <span class="n">getchar</span><span class="p">();</span>
+  <span class="k">while</span> <span class="p">(</span><span class="n">LastChar</span> <span class="o">!=</span> <span class="n">EOF</span> <span class="o">&&</span> <span class="n">LastChar</span> <span class="o">!=</span> <span class="sc">'\n'</span> <span class="o">&&</span> <span class="n">LastChar</span> <span class="o">!=</span> <span class="sc">'\r'</span><span class="p">);</span>
+
+  <span class="k">if</span> <span class="p">(</span><span class="n">LastChar</span> <span class="o">!=</span> <span class="n">EOF</span><span class="p">)</span>
+    <span class="k">return</span> <span class="n">gettok</span><span class="p">();</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>We handle comments by skipping to the end of the line and then return
+the next token. Finally, if the input doesn’t match one of the above
+cases, it is either an operator character like ‘+’ or the end of the
+file. These are handled with this code:</p>
+<div class="highlight-c++"><div class="highlight"><pre>  <span class="c1">// Check for end of file.  Don't eat the EOF.</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">LastChar</span> <span class="o">==</span> <span class="n">EOF</span><span class="p">)</span>
+    <span class="k">return</span> <span class="n">tok_eof</span><span class="p">;</span>
+
+  <span class="c1">// Otherwise, just return the character as its ascii value.</span>
+  <span class="kt">int</span> <span class="n">ThisChar</span> <span class="o">=</span> <span class="n">LastChar</span><span class="p">;</span>
+  <span class="n">LastChar</span> <span class="o">=</span> <span class="n">getchar</span><span class="p">();</span>
+  <span class="k">return</span> <span class="n">ThisChar</span><span class="p">;</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>With this, we have the complete lexer for the basic Kaleidoscope
+language (the <a class="reference external" href="LangImpl02.html#full-code-listing">full code listing</a> for the Lexer
+is available in the <a class="reference external" href="LangImpl02.html">next chapter</a> of the tutorial).
+Next we’ll <a class="reference external" href="LangImpl02.html">build a simple parser that uses this to build an Abstract
+Syntax Tree</a>. When we have that, we’ll include a
+driver so that you can use the lexer and parser together.</p>
+<p><a class="reference external" href="LangImpl02.html">Next: Implementing a Parser and AST</a></p>
+</div>
+</div>
+
+
+          </div>
+      </div>
+      <div class="clearer"></div>
+    </div>
+    <div class="related">
+      <h3>Navigation</h3>
+      <ul>
+        <li class="right" style="margin-right: 10px">
+          <a href="../genindex.html" title="General Index"
+             >index</a></li>
+        <li class="right" >
+          <a href="LangImpl02.html" title="2. Kaleidoscope: Implementing a Parser and AST"
+             >next</a> |</li>
+        <li class="right" >
+          <a href="index.html" title="LLVM Tutorial: Table of Contents"
+             >previous</a> |</li>
+  <li><a href="http://llvm.org/">LLVM Home</a> | </li>
+  <li><a href="../index.html">Documentation</a>»</li>
+
+          <li><a href="index.html" >LLVM Tutorial: Table of Contents</a> »</li> 
+      </ul>
+    </div>
+    <div class="footer">
+        © Copyright 2003-2016, LLVM Project.
+      Last updated on 2016-12-21.
+      Created using <a href="http://sphinx-doc.org/">Sphinx</a> 1.2.2.
+    </div>
+  </body>
+</html>
\ No newline at end of file




More information about the llvm-commits mailing list