[www-releases] r238135 - Add 3.6.1 LLVM Docs.

Tom Stellard thomas.stellard at amd.com
Mon May 25 06:53:05 PDT 2015


Added: www-releases/trunk/3.6.1/docs/_sources/tutorial/OCamlLangImpl4.txt
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/_sources/tutorial/OCamlLangImpl4.txt?rev=238135&view=auto
==============================================================================
--- www-releases/trunk/3.6.1/docs/_sources/tutorial/OCamlLangImpl4.txt (added)
+++ www-releases/trunk/3.6.1/docs/_sources/tutorial/OCamlLangImpl4.txt Mon May 25 08:53:02 2015
@@ -0,0 +1,915 @@
+==============================================
+Kaleidoscope: Adding JIT and Optimizer Support
+==============================================
+
+.. contents::
+   :local:
+
+Chapter 4 Introduction
+======================
+
+Welcome to Chapter 4 of the "`Implementing a language with
+LLVM <index.html>`_" tutorial. Chapters 1-3 described the implementation
+of a simple language and added support for generating LLVM IR. This
+chapter describes two new techniques: adding optimizer support to your
+language, and adding JIT compiler support. These additions will
+demonstrate how to get nice, efficient code for the Kaleidoscope
+language.
+
+Trivial Constant Folding
+========================
+
+**Note:** the default ``IRBuilder`` now always includes the constant
+folding optimisations below.
+
+Our demonstration for Chapter 3 is elegant and easy to extend.
+Unfortunately, it does not produce wonderful code. For example, when
+compiling simple code, we don't get obvious optimizations:
+
+::
+
+    ready> def test(x) 1+2+x;
+    Read function definition:
+    define double @test(double %x) {
+    entry:
+            %addtmp = fadd double 1.000000e+00, 2.000000e+00
+            %addtmp1 = fadd double %addtmp, %x
+            ret double %addtmp1
+    }
+
+This code is a very, very literal transcription of the AST built by
+parsing the input. As such, this transcription lacks optimizations like
+constant folding (we'd like to get "``add x, 3.0``" in the example
+above) as well as other more important optimizations. Constant folding,
+in particular, is a very common and very important optimization: so much
+so that many language implementors implement constant folding support in
+their AST representation.
+
+With LLVM, you don't need this support in the AST. Since all calls to
+build LLVM IR go through the LLVM builder, it would be nice if the
+builder itself checked to see if there was a constant folding
+opportunity when you call it. If so, it could just do the constant fold
+and return the constant instead of creating an instruction. This is
+exactly what the ``LLVMFoldingBuilder`` class does.
+
+All we did was switch from ``LLVMBuilder`` to ``LLVMFoldingBuilder``.
+Though we change no other code, we now have all of our instructions
+implicitly constant folded without us having to do anything about it.
+For example, the input above now compiles to:
+
+::
+
+    ready> def test(x) 1+2+x;
+    Read function definition:
+    define double @test(double %x) {
+    entry:
+            %addtmp = fadd double 3.000000e+00, %x
+            ret double %addtmp
+    }
+
+Well, that was easy :). In practice, we recommend always using
+``LLVMFoldingBuilder`` when generating code like this. It has no
+"syntactic overhead" for its use (you don't have to uglify your compiler
+with constant checks everywhere) and it can dramatically reduce the
+amount of LLVM IR that is generated in some cases (particular for
+languages with a macro preprocessor or that use a lot of constants).
+
+On the other hand, the ``LLVMFoldingBuilder`` is limited by the fact
+that it does all of its analysis inline with the code as it is built. If
+you take a slightly more complex example:
+
+::
+
+    ready> def test(x) (1+2+x)*(x+(1+2));
+    ready> Read function definition:
+    define double @test(double %x) {
+    entry:
+            %addtmp = fadd double 3.000000e+00, %x
+            %addtmp1 = fadd double %x, 3.000000e+00
+            %multmp = fmul double %addtmp, %addtmp1
+            ret double %multmp
+    }
+
+In this case, the LHS and RHS of the multiplication are the same value.
+We'd really like to see this generate "``tmp = x+3; result = tmp*tmp;``"
+instead of computing "``x*3``" twice.
+
+Unfortunately, no amount of local analysis will be able to detect and
+correct this. This requires two transformations: reassociation of
+expressions (to make the add's lexically identical) and Common
+Subexpression Elimination (CSE) to delete the redundant add instruction.
+Fortunately, LLVM provides a broad range of optimizations that you can
+use, in the form of "passes".
+
+LLVM Optimization Passes
+========================
+
+LLVM provides many optimization passes, which do many different sorts of
+things and have different tradeoffs. Unlike other systems, LLVM doesn't
+hold to the mistaken notion that one set of optimizations is right for
+all languages and for all situations. LLVM allows a compiler implementor
+to make complete decisions about what optimizations to use, in which
+order, and in what situation.
+
+As a concrete example, LLVM supports both "whole module" passes, which
+look across as large of body of code as they can (often a whole file,
+but if run at link time, this can be a substantial portion of the whole
+program). It also supports and includes "per-function" passes which just
+operate on a single function at a time, without looking at other
+functions. For more information on passes and how they are run, see the
+`How to Write a Pass <../WritingAnLLVMPass.html>`_ document and the
+`List of LLVM Passes <../Passes.html>`_.
+
+For Kaleidoscope, we are currently generating functions on the fly, one
+at a time, as the user types them in. We aren't shooting for the
+ultimate optimization experience in this setting, but we also want to
+catch the easy and quick stuff where possible. As such, we will choose
+to run a few per-function optimizations as the user types the function
+in. If we wanted to make a "static Kaleidoscope compiler", we would use
+exactly the code we have now, except that we would defer running the
+optimizer until the entire file has been parsed.
+
+In order to get per-function optimizations going, we need to set up a
+`Llvm.PassManager <../WritingAnLLVMPass.html#passmanager>`_ to hold and
+organize the LLVM optimizations that we want to run. Once we have that,
+we can add a set of optimizations to run. The code looks like this:
+
+.. code-block:: ocaml
+
+      (* 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_combining 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;
+
+The meat of the matter here, is the definition of "``the_fpm``". It
+requires a pointer to the ``the_module`` to construct itself. Once it is
+set up, we use a series of "add" calls to add a bunch of LLVM passes.
+The first pass is basically boilerplate, it adds a pass so that later
+optimizations know how the data structures in the program are laid out.
+The "``the_execution_engine``" variable is related to the JIT, which we
+will get to in the next section.
+
+In this case, we choose to add 4 optimization passes. The passes we
+chose here are a pretty standard set of "cleanup" optimizations that are
+useful for a wide variety of code. I won't delve into what they do but,
+believe me, they are a good starting place :).
+
+Once the ``Llvm.PassManager.`` is set up, we need to make use of it. We
+do this by running it after our newly created function is constructed
+(in ``Codegen.codegen_func``), but before it is returned to the client:
+
+.. code-block:: ocaml
+
+    let codegen_func the_fpm = function
+          ...
+          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
+
+As you can see, this is pretty straightforward. The ``the_fpm``
+optimizes and updates the LLVM Function\* in place, improving
+(hopefully) its body. With this in place, we can try our test above
+again:
+
+::
+
+    ready> def test(x) (1+2+x)*(x+(1+2));
+    ready> Read function definition:
+    define double @test(double %x) {
+    entry:
+            %addtmp = fadd double %x, 3.000000e+00
+            %multmp = fmul double %addtmp, %addtmp
+            ret double %multmp
+    }
+
+As expected, we now get our nicely optimized code, saving a floating
+point add instruction from every execution of this function.
+
+LLVM provides a wide variety of optimizations that can be used in
+certain circumstances. Some `documentation about the various
+passes <../Passes.html>`_ is available, but it isn't very complete.
+Another good source of ideas can come from looking at the passes that
+``Clang`` runs to get started. The "``opt``" tool allows you to
+experiment with passes from the command line, so you can see if they do
+anything.
+
+Now that we have reasonable code coming out of our front-end, lets talk
+about executing it!
+
+Adding a JIT Compiler
+=====================
+
+Code that is available in LLVM IR can have a wide variety of tools
+applied to it. For example, you can run optimizations on it (as we did
+above), you can dump it out in textual or binary forms, you can compile
+the code to an assembly file (.s) for some target, or you can JIT
+compile it. The nice thing about the LLVM IR representation is that it
+is the "common currency" between many different parts of the compiler.
+
+In this section, we'll add JIT compiler support to our interpreter. The
+basic idea that we want for Kaleidoscope is to have the user enter
+function bodies as they do now, but immediately evaluate the top-level
+expressions they type in. For example, if they type in "1 + 2;", we
+should evaluate and print out 3. If they define a function, they should
+be able to call it from the command line.
+
+In order to do this, we first declare and initialize the JIT. This is
+done by adding a global variable and a call in ``main``:
+
+.. code-block:: ocaml
+
+    ...
+    let main () =
+      ...
+      (* Create the JIT. *)
+      let the_execution_engine = ExecutionEngine.create Codegen.the_module in
+      ...
+
+This creates an abstract "Execution Engine" which can be either a JIT
+compiler or the LLVM interpreter. LLVM will automatically pick a JIT
+compiler for you if one is available for your platform, otherwise it
+will fall back to the interpreter.
+
+Once the ``Llvm_executionengine.ExecutionEngine.t`` is created, the JIT
+is ready to be used. There are a variety of APIs that are useful, but
+the simplest one is the
+"``Llvm_executionengine.ExecutionEngine.run_function``" function. This
+method JIT compiles the specified LLVM Function and returns a function
+pointer to the generated machine code. In our case, this means that we
+can change the code that parses a top-level expression to look like
+this:
+
+.. code-block:: ocaml
+
+                (* 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 ();
+
+Recall that we compile top-level expressions into a self-contained LLVM
+function that takes no arguments and returns the computed double.
+Because the LLVM JIT compiler matches the native platform ABI, this
+means that you can just cast the result pointer to a function pointer of
+that type and call it directly. This means, there is no difference
+between JIT compiled code and native machine code that is statically
+linked into your application.
+
+With just these two changes, lets see how Kaleidoscope works now!
+
+::
+
+    ready> 4+5;
+    define double @""() {
+    entry:
+            ret double 9.000000e+00
+    }
+
+    Evaluated to 9.000000
+
+Well this looks like it is basically working. The dump of the function
+shows the "no argument function that always returns double" that we
+synthesize for each top level expression that is typed in. This
+demonstrates very basic functionality, but can we do more?
+
+::
+
+    ready> def testfunc(x y) x + y*2;
+    Read function definition:
+    define double @testfunc(double %x, double %y) {
+    entry:
+            %multmp = fmul double %y, 2.000000e+00
+            %addtmp = fadd double %multmp, %x
+            ret double %addtmp
+    }
+
+    ready> testfunc(4, 10);
+    define double @""() {
+    entry:
+            %calltmp = call double @testfunc(double 4.000000e+00, double 1.000000e+01)
+            ret double %calltmp
+    }
+
+    Evaluated to 24.000000
+
+This illustrates that we can now call user code, but there is something
+a bit subtle going on here. Note that we only invoke the JIT on the
+anonymous functions that *call testfunc*, but we never invoked it on
+*testfunc* itself. What actually happened here is that the JIT scanned
+for all non-JIT'd functions transitively called from the anonymous
+function and compiled all of them before returning from
+``run_function``.
+
+The JIT provides a number of other more advanced interfaces for things
+like freeing allocated machine code, rejit'ing functions to update them,
+etc. However, even with this simple code, we get some surprisingly
+powerful capabilities - check this out (I removed the dump of the
+anonymous functions, you should get the idea by now :) :
+
+::
+
+    ready> extern sin(x);
+    Read extern:
+    declare double @sin(double)
+
+    ready> extern cos(x);
+    Read extern:
+    declare double @cos(double)
+
+    ready> sin(1.0);
+    Evaluated to 0.841471
+
+    ready> def foo(x) sin(x)*sin(x) + cos(x)*cos(x);
+    Read function definition:
+    define double @foo(double %x) {
+    entry:
+            %calltmp = call double @sin(double %x)
+            %multmp = fmul double %calltmp, %calltmp
+            %calltmp2 = call double @cos(double %x)
+            %multmp4 = fmul double %calltmp2, %calltmp2
+            %addtmp = fadd double %multmp, %multmp4
+            ret double %addtmp
+    }
+
+    ready> foo(4.0);
+    Evaluated to 1.000000
+
+Whoa, how does the JIT know about sin and cos? The answer is
+surprisingly simple: in this example, the JIT started execution of a
+function and got to a function call. It realized that the function was
+not yet JIT compiled and invoked the standard set of routines to resolve
+the function. In this case, there is no body defined for the function,
+so the JIT ended up calling "``dlsym("sin")``" on the Kaleidoscope
+process itself. Since "``sin``" is defined within the JIT's address
+space, it simply patches up calls in the module to call the libm version
+of ``sin`` directly.
+
+The LLVM JIT provides a number of interfaces (look in the
+``llvm_executionengine.mli`` file) for controlling how unknown functions
+get resolved. It allows you to establish explicit mappings between IR
+objects and addresses (useful for LLVM global variables that you want to
+map to static tables, for example), allows you to dynamically decide on
+the fly based on the function name, and even allows you to have the JIT
+compile functions lazily the first time they're called.
+
+One interesting application of this is that we can now extend the
+language by writing arbitrary C code to implement operations. For
+example, if we add:
+
+.. code-block:: c++
+
+    /* putchard - putchar that takes a double and returns 0. */
+    extern "C"
+    double putchard(double X) {
+      putchar((char)X);
+      return 0;
+    }
+
+Now we can produce simple output to the console by using things like:
+"``extern putchard(x); putchard(120);``", which prints a lowercase 'x'
+on the console (120 is the ASCII code for 'x'). Similar code could be
+used to implement file I/O, console input, and many other capabilities
+in Kaleidoscope.
+
+This completes the JIT and optimizer chapter of the Kaleidoscope
+tutorial. At this point, we can compile a non-Turing-complete
+programming language, optimize and JIT compile it in a user-driven way.
+Next up we'll look into `extending the language with control flow
+constructs <OCamlLangImpl5.html>`_, tackling some interesting LLVM IR
+issues along the way.
+
+Full Code Listing
+=================
+
+Here is the complete code listing for our running example, enhanced with
+the LLVM JIT and optimizer. 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
+
+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 >]
+              | 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
+
+        (* 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 *)
+        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
+
+          | [< >] -> 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
+
+        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: control flow <OCamlLangImpl5.html>`_
+

Added: www-releases/trunk/3.6.1/docs/_sources/tutorial/OCamlLangImpl5.txt
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/_sources/tutorial/OCamlLangImpl5.txt?rev=238135&view=auto
==============================================================================
--- www-releases/trunk/3.6.1/docs/_sources/tutorial/OCamlLangImpl5.txt (added)
+++ www-releases/trunk/3.6.1/docs/_sources/tutorial/OCamlLangImpl5.txt Mon May 25 08:53:02 2015
@@ -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#ViewGraph>`_ and you'll
+see this graph:
+
+.. figure:: LangImpl5-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 block 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.6.1/docs/_sources/tutorial/OCamlLangImpl6.txt
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/_sources/tutorial/OCamlLangImpl6.txt?rev=238135&view=auto
==============================================================================
--- www-releases/trunk/3.6.1/docs/_sources/tutorial/OCamlLangImpl6.txt (added)
+++ www-releases/trunk/3.6.1/docs/_sources/tutorial/OCamlLangImpl6.txt Mon May 25 08:53:02 2015
@@ -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 <#example>`_. 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#iflexer>`_. 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 mandleconverger(real imag iters creal cimag)
+      if iters > 255 | (real*real + imag*imag > 4) then
+        iters
+      else
+        mandleconverger(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 mandleconverge(real imag)
+      mandleconverger(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 mandlebrot 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(mandleconverge(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 mandlebrot 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.6.1/docs/_sources/tutorial/OCamlLangImpl7.txt
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/_sources/tutorial/OCamlLangImpl7.txt?rev=238135&view=auto
==============================================================================
--- www-releases/trunk/3.6.1/docs/_sources/tutorial/OCamlLangImpl7.txt (added)
+++ www-releases/trunk/3.6.1/docs/_sources/tutorial/OCamlLangImpl7.txt Mon May 25 08:53:02 2015
@@ -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#i_alloca>`_:
+
+.. 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#t_classifications>`_ 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 "scalarrepl" 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 <#code>`_
+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#forcodegen>`_. 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.6.1/docs/_sources/tutorial/OCamlLangImpl8.txt
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/_sources/tutorial/OCamlLangImpl8.txt?rev=238135&view=auto
==============================================================================
--- www-releases/trunk/3.6.1/docs/_sources/tutorial/OCamlLangImpl8.txt (added)
+++ www-releases/trunk/3.6.1/docs/_sources/tutorial/OCamlLangImpl8.txt Mon May 25 08:53:02 2015
@@ -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#i_getelementptr>`_ 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 `llvmdev mailing
+list <http://lists.cs.uiuc.edu/mailman/listinfo/llvmdev>`_: 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 `llvmdev
+mailing list <http://lists.cs.uiuc.edu/mailman/listinfo/llvmdev>`_ 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 llvmdev 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.6.1/docs/_sources/tutorial/index.txt
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/_sources/tutorial/index.txt?rev=238135&view=auto
==============================================================================
--- www-releases/trunk/3.6.1/docs/_sources/tutorial/index.txt (added)
+++ www-releases/trunk/3.6.1/docs/_sources/tutorial/index.txt Mon May 25 08:53:02 2015
@@ -0,0 +1,43 @@
+================================
+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*
+
+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.6.1/docs/_sources/yaml2obj.txt
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/_sources/yaml2obj.txt?rev=238135&view=auto
==============================================================================
--- www-releases/trunk/3.6.1/docs/_sources/yaml2obj.txt (added)
+++ www-releases/trunk/3.6.1/docs/_sources/yaml2obj.txt Mon May 25 08:53:02 2015
@@ -0,0 +1,220 @@
+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_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.6.1/docs/_static/ajax-loader.gif
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/_static/ajax-loader.gif?rev=238135&view=auto
==============================================================================
Binary file - no diff available.

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

Added: www-releases/trunk/3.6.1/docs/_static/basic.css
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/_static/basic.css?rev=238135&view=auto
==============================================================================
--- www-releases/trunk/3.6.1/docs/_static/basic.css (added)
+++ www-releases/trunk/3.6.1/docs/_static/basic.css Mon May 25 08:53:02 2015
@@ -0,0 +1,540 @@
+/*
+ * basic.css
+ * ~~~~~~~~~
+ *
+ * Sphinx stylesheet -- basic theme.
+ *
+ * :copyright: Copyright 2007-2011 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;
+}
+
+/* -- 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;
+}
+
+.refcount {
+    color: #060;
+}
+
+.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.6.1/docs/_static/comment-bright.png
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/_static/comment-bright.png?rev=238135&view=auto
==============================================================================
Binary file - no diff available.

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

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

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

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

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

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

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

Added: www-releases/trunk/3.6.1/docs/_static/doctools.js
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/_static/doctools.js?rev=238135&view=auto
==============================================================================
--- www-releases/trunk/3.6.1/docs/_static/doctools.js (added)
+++ www-releases/trunk/3.6.1/docs/_static/doctools.js Mon May 25 08:53:02 2015
@@ -0,0 +1,247 @@
+/*
+ * doctools.js
+ * ~~~~~~~~~~~
+ *
+ * Sphinx JavaScript utilities for all documentation.
+ *
+ * :copyright: Copyright 2007-2011 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;
+};
+
+/**
+ * small function to check if an array contains
+ * a given item.
+ */
+jQuery.contains = function(arr, item) {
+  for (var i = 0; i < arr.length; i++) {
+    if (arr[i] == item)
+      return true;
+  }
+  return false;
+};
+
+/**
+ * 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');
+      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.6.1/docs/_static/down-pressed.png
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/_static/down-pressed.png?rev=238135&view=auto
==============================================================================
Binary file - no diff available.

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

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

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

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

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

Added: www-releases/trunk/3.6.1/docs/_static/jquery.js
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/_static/jquery.js?rev=238135&view=auto
==============================================================================
--- www-releases/trunk/3.6.1/docs/_static/jquery.js (added)
+++ www-releases/trunk/3.6.1/docs/_static/jquery.js Mon May 25 08:53:02 2015
@@ -0,0 +1,154 @@
+/*!
+ * jQuery JavaScript Library v1.4.2
+ * http://jquery.com/
+ *
+ * Copyright 2010, John Resig
+ * Dual licensed under the MIT or GPL Version 2 licenses.
+ * http://jquery.org/license
+ *
+ * Includes Sizzle.js
+ * http://sizzlejs.com/
+ * Copyright 2010, The Dojo Foundation
+ * Released under the MIT, BSD, and GPL Licenses.
+ *
+ * Date: Sat Feb 13 22:33:48 2010 -0500
+ */
+(function(A,w){function ma(){if(!c.isReady){try{s.documentElement.doScroll("left")}catch(a){setTimeout(ma,1);return}c.ready()}}function Qa(a,b){b.src?c.ajax({url:b.src,async:false,dataType:"script"}):c.globalEval(b.text||b.textContent||b.innerHTML||"");b.parentNode&&b.parentNode.removeChild(b)}function X(a,b,d,f,e,j){var i=a.length;if(typeof b==="object"){for(var o in b)X(a,o,b[o],f,e,d);return a}if(d!==w){f=!j&&f&&c.isFunction(d);for(o=0;o<i;o++)e(a[o],b,f?d.call(a[o],o,e(a[o],b)):d,j);return a}return i?
+e(a[0],b):w}function J(){return(new Date).getTime()}function Y(){return false}function Z(){return true}function na(a,b,d){d[0].type=a;return c.event.handle.apply(b,d)}function oa(a){var b,d=[],f=[],e=arguments,j,i,o,k,n,r;i=c.data(this,"events");if(!(a.liveFired===this||!i||!i.live||a.button&&a.type==="click")){a.liveFired=this;var u=i.live.slice(0);for(k=0;k<u.length;k++){i=u[k];i.origType.replace(O,"")===a.type?f.push(i.selector):u.splice(k--,1)}j=c(a.target).closest(f,a.currentTarget);n=0;for(r=
+j.length;n<r;n++)for(k=0;k<u.length;k++){i=u[k];if(j[n].selector===i.selector){o=j[n].elem;f=null;if(i.preType==="mouseenter"||i.preType==="mouseleave")f=c(a.relatedTarget).closest(i.selector)[0];if(!f||f!==o)d.push({elem:o,handleObj:i})}}n=0;for(r=d.length;n<r;n++){j=d[n];a.currentTarget=j.elem;a.data=j.handleObj.data;a.handleObj=j.handleObj;if(j.handleObj.origHandler.apply(j.elem,e)===false){b=false;break}}return b}}function pa(a,b){return"live."+(a&&a!=="*"?a+".":"")+b.replace(/\./g,"`").replace(/ /g,
+"&")}function qa(a){return!a||!a.parentNode||a.parentNode.nodeType===11}function ra(a,b){var d=0;b.each(function(){if(this.nodeName===(a[d]&&a[d].nodeName)){var f=c.data(a[d++]),e=c.data(this,f);if(f=f&&f.events){delete e.handle;e.events={};for(var j in f)for(var i in f[j])c.event.add(this,j,f[j][i],f[j][i].data)}}})}function sa(a,b,d){var f,e,j;b=b&&b[0]?b[0].ownerDocument||b[0]:s;if(a.length===1&&typeof a[0]==="string"&&a[0].length<512&&b===s&&!ta.test(a[0])&&(c.support.checkClone||!ua.test(a[0]))){e=
+true;if(j=c.fragments[a[0]])if(j!==1)f=j}if(!f){f=b.createDocumentFragment();c.clean(a,b,f,d)}if(e)c.fragments[a[0]]=j?f:1;return{fragment:f,cacheable:e}}function K(a,b){var d={};c.each(va.concat.apply([],va.slice(0,b)),function(){d[this]=a});return d}function wa(a){return"scrollTo"in a&&a.document?a:a.nodeType===9?a.defaultView||a.parentWindow:false}var c=function(a,b){return new c.fn.init(a,b)},Ra=A.jQuery,Sa=A.$,s=A.document,T,Ta=/^[^<]*(<[\w\W]+>)[^>]*$|^#([\w-]+)$/,Ua=/^.[^:#\[\.,]*$/,Va=/\S/,
+Wa=/^(\s|\u00A0)+|(\s|\u00A0)+$/g,Xa=/^<(\w+)\s*\/?>(?:<\/\1>)?$/,P=navigator.userAgent,xa=false,Q=[],L,$=Object.prototype.toString,aa=Object.prototype.hasOwnProperty,ba=Array.prototype.push,R=Array.prototype.slice,ya=Array.prototype.indexOf;c.fn=c.prototype={init:function(a,b){var d,f;if(!a)return this;if(a.nodeType){this.context=this[0]=a;this.length=1;return this}if(a==="body"&&!b){this.context=s;this[0]=s.body;this.selector="body";this.length=1;return this}if(typeof a==="string")if((d=Ta.exec(a))&&
+(d[1]||!b))if(d[1]){f=b?b.ownerDocument||b:s;if(a=Xa.exec(a))if(c.isPlainObject(b)){a=[s.createElement(a[1])];c.fn.attr.call(a,b,true)}else a=[f.createElement(a[1])];else{a=sa([d[1]],[f]);a=(a.cacheable?a.fragment.cloneNode(true):a.fragment).childNodes}return c.merge(this,a)}else{if(b=s.getElementById(d[2])){if(b.id!==d[2])return T.find(a);this.length=1;this[0]=b}this.context=s;this.selector=a;return this}else if(!b&&/^\w+$/.test(a)){this.selector=a;this.context=s;a=s.getElementsByTagName(a);return c.merge(this,
+a)}else return!b||b.jquery?(b||T).find(a):c(b).find(a);else if(c.isFunction(a))return T.ready(a);if(a.selector!==w){this.selector=a.selector;this.context=a.context}return c.makeArray(a,this)},selector:"",jquery:"1.4.2",length:0,size:function(){return this.length},toArray:function(){return R.call(this,0)},get:function(a){return a==null?this.toArray():a<0?this.slice(a)[0]:this[a]},pushStack:function(a,b,d){var f=c();c.isArray(a)?ba.apply(f,a):c.merge(f,a);f.prevObject=this;f.context=this.context;if(b===
+"find")f.selector=this.selector+(this.selector?" ":"")+d;else if(b)f.selector=this.selector+"."+b+"("+d+")";return f},each:function(a,b){return c.each(this,a,b)},ready:function(a){c.bindReady();if(c.isReady)a.call(s,c);else Q&&Q.push(a);return this},eq:function(a){return a===-1?this.slice(a):this.slice(a,+a+1)},first:function(){return this.eq(0)},last:function(){return this.eq(-1)},slice:function(){return this.pushStack(R.apply(this,arguments),"slice",R.call(arguments).join(","))},map:function(a){return this.pushStack(c.map(this,
+function(b,d){return a.call(b,d,b)}))},end:function(){return this.prevObject||c(null)},push:ba,sort:[].sort,splice:[].splice};c.fn.init.prototype=c.fn;c.extend=c.fn.extend=function(){var a=arguments[0]||{},b=1,d=arguments.length,f=false,e,j,i,o;if(typeof a==="boolean"){f=a;a=arguments[1]||{};b=2}if(typeof a!=="object"&&!c.isFunction(a))a={};if(d===b){a=this;--b}for(;b<d;b++)if((e=arguments[b])!=null)for(j in e){i=a[j];o=e[j];if(a!==o)if(f&&o&&(c.isPlainObject(o)||c.isArray(o))){i=i&&(c.isPlainObject(i)||
+c.isArray(i))?i:c.isArray(o)?[]:{};a[j]=c.extend(f,i,o)}else if(o!==w)a[j]=o}return a};c.extend({noConflict:function(a){A.$=Sa;if(a)A.jQuery=Ra;return c},isReady:false,ready:function(){if(!c.isReady){if(!s.body)return setTimeout(c.ready,13);c.isReady=true;if(Q){for(var a,b=0;a=Q[b++];)a.call(s,c);Q=null}c.fn.triggerHandler&&c(s).triggerHandler("ready")}},bindReady:function(){if(!xa){xa=true;if(s.readyState==="complete")return c.ready();if(s.addEventListener){s.addEventListener("DOMContentLoaded",
+L,false);A.addEventListener("load",c.ready,false)}else if(s.attachEvent){s.attachEvent("onreadystatechange",L);A.attachEvent("onload",c.ready);var a=false;try{a=A.frameElement==null}catch(b){}s.documentElement.doScroll&&a&&ma()}}},isFunction:function(a){return $.call(a)==="[object Function]"},isArray:function(a){return $.call(a)==="[object Array]"},isPlainObject:function(a){if(!a||$.call(a)!=="[object Object]"||a.nodeType||a.setInterval)return false;if(a.constructor&&!aa.call(a,"constructor")&&!aa.call(a.constructor.prototype,
+"isPrototypeOf"))return false;var b;for(b in a);return b===w||aa.call(a,b)},isEmptyObject:function(a){for(var b in a)return false;return true},error:function(a){throw a;},parseJSON:function(a){if(typeof a!=="string"||!a)return null;a=c.trim(a);if(/^[\],:{}\s]*$/.test(a.replace(/\\(?:["\\\/bfnrt]|u[0-9a-fA-F]{4})/g,"@").replace(/"[^"\\\n\r]*"|true|false|null|-?\d+(?:\.\d*)?(?:[eE][+\-]?\d+)?/g,"]").replace(/(?:^|:|,)(?:\s*\[)+/g,"")))return A.JSON&&A.JSON.parse?A.JSON.parse(a):(new Function("return "+
+a))();else c.error("Invalid JSON: "+a)},noop:function(){},globalEval:function(a){if(a&&Va.test(a)){var b=s.getElementsByTagName("head")[0]||s.documentElement,d=s.createElement("script");d.type="text/javascript";if(c.support.scriptEval)d.appendChild(s.createTextNode(a));else d.text=a;b.insertBefore(d,b.firstChild);b.removeChild(d)}},nodeName:function(a,b){return a.nodeName&&a.nodeName.toUpperCase()===b.toUpperCase()},each:function(a,b,d){var f,e=0,j=a.length,i=j===w||c.isFunction(a);if(d)if(i)for(f in a){if(b.apply(a[f],
+d)===false)break}else for(;e<j;){if(b.apply(a[e++],d)===false)break}else if(i)for(f in a){if(b.call(a[f],f,a[f])===false)break}else for(d=a[0];e<j&&b.call(d,e,d)!==false;d=a[++e]);return a},trim:function(a){return(a||"").replace(Wa,"")},makeArray:function(a,b){b=b||[];if(a!=null)a.length==null||typeof a==="string"||c.isFunction(a)||typeof a!=="function"&&a.setInterval?ba.call(b,a):c.merge(b,a);return b},inArray:function(a,b){if(b.indexOf)return b.indexOf(a);for(var d=0,f=b.length;d<f;d++)if(b[d]===
+a)return d;return-1},merge:function(a,b){var d=a.length,f=0;if(typeof b.length==="number")for(var e=b.length;f<e;f++)a[d++]=b[f];else for(;b[f]!==w;)a[d++]=b[f++];a.length=d;return a},grep:function(a,b,d){for(var f=[],e=0,j=a.length;e<j;e++)!d!==!b(a[e],e)&&f.push(a[e]);return f},map:function(a,b,d){for(var f=[],e,j=0,i=a.length;j<i;j++){e=b(a[j],j,d);if(e!=null)f[f.length]=e}return f.concat.apply([],f)},guid:1,proxy:function(a,b,d){if(arguments.length===2)if(typeof b==="string"){d=a;a=d[b];b=w}else if(b&&
+!c.isFunction(b)){d=b;b=w}if(!b&&a)b=function(){return a.apply(d||this,arguments)};if(a)b.guid=a.guid=a.guid||b.guid||c.guid++;return b},uaMatch:function(a){a=a.toLowerCase();a=/(webkit)[ \/]([\w.]+)/.exec(a)||/(opera)(?:.*version)?[ \/]([\w.]+)/.exec(a)||/(msie) ([\w.]+)/.exec(a)||!/compatible/.test(a)&&/(mozilla)(?:.*? rv:([\w.]+))?/.exec(a)||[];return{browser:a[1]||"",version:a[2]||"0"}},browser:{}});P=c.uaMatch(P);if(P.browser){c.browser[P.browser]=true;c.browser.version=P.version}if(c.browser.webkit)c.browser.safari=
+true;if(ya)c.inArray=function(a,b){return ya.call(b,a)};T=c(s);if(s.addEventListener)L=function(){s.removeEventListener("DOMContentLoaded",L,false);c.ready()};else if(s.attachEvent)L=function(){if(s.readyState==="complete"){s.detachEvent("onreadystatechange",L);c.ready()}};(function(){c.support={};var a=s.documentElement,b=s.createElement("script"),d=s.createElement("div"),f="script"+J();d.style.display="none";d.innerHTML="   <link/><table></table><a href='/a' style='color:red;float:left;opacity:.55;'>a</a><input type='checkbox'/>";
+var e=d.getElementsByTagName("*"),j=d.getElementsByTagName("a")[0];if(!(!e||!e.length||!j)){c.support={leadingWhitespace:d.firstChild.nodeType===3,tbody:!d.getElementsByTagName("tbody").length,htmlSerialize:!!d.getElementsByTagName("link").length,style:/red/.test(j.getAttribute("style")),hrefNormalized:j.getAttribute("href")==="/a",opacity:/^0.55$/.test(j.style.opacity),cssFloat:!!j.style.cssFloat,checkOn:d.getElementsByTagName("input")[0].value==="on",optSelected:s.createElement("select").appendChild(s.createElement("option")).selected,
+parentNode:d.removeChild(d.appendChild(s.createElement("div"))).parentNode===null,deleteExpando:true,checkClone:false,scriptEval:false,noCloneEvent:true,boxModel:null};b.type="text/javascript";try{b.appendChild(s.createTextNode("window."+f+"=1;"))}catch(i){}a.insertBefore(b,a.firstChild);if(A[f]){c.support.scriptEval=true;delete A[f]}try{delete b.test}catch(o){c.support.deleteExpando=false}a.removeChild(b);if(d.attachEvent&&d.fireEvent){d.attachEvent("onclick",function k(){c.support.noCloneEvent=
+false;d.detachEvent("onclick",k)});d.cloneNode(true).fireEvent("onclick")}d=s.createElement("div");d.innerHTML="<input type='radio' name='radiotest' checked='checked'/>";a=s.createDocumentFragment();a.appendChild(d.firstChild);c.support.checkClone=a.cloneNode(true).cloneNode(true).lastChild.checked;c(function(){var k=s.createElement("div");k.style.width=k.style.paddingLeft="1px";s.body.appendChild(k);c.boxModel=c.support.boxModel=k.offsetWidth===2;s.body.removeChild(k).style.display="none"});a=function(k){var n=
+s.createElement("div");k="on"+k;var r=k in n;if(!r){n.setAttribute(k,"return;");r=typeof n[k]==="function"}return r};c.support.submitBubbles=a("submit");c.support.changeBubbles=a("change");a=b=d=e=j=null}})();c.props={"for":"htmlFor","class":"className",readonly:"readOnly",maxlength:"maxLength",cellspacing:"cellSpacing",rowspan:"rowSpan",colspan:"colSpan",tabindex:"tabIndex",usemap:"useMap",frameborder:"frameBorder"};var G="jQuery"+J(),Ya=0,za={};c.extend({cache:{},expando:G,noData:{embed:true,object:true,
+applet:true},data:function(a,b,d){if(!(a.nodeName&&c.noData[a.nodeName.toLowerCase()])){a=a==A?za:a;var f=a[G],e=c.cache;if(!f&&typeof b==="string"&&d===w)return null;f||(f=++Ya);if(typeof b==="object"){a[G]=f;e[f]=c.extend(true,{},b)}else if(!e[f]){a[G]=f;e[f]={}}a=e[f];if(d!==w)a[b]=d;return typeof b==="string"?a[b]:a}},removeData:function(a,b){if(!(a.nodeName&&c.noData[a.nodeName.toLowerCase()])){a=a==A?za:a;var d=a[G],f=c.cache,e=f[d];if(b){if(e){delete e[b];c.isEmptyObject(e)&&c.removeData(a)}}else{if(c.support.deleteExpando)delete a[c.expando];
+else a.removeAttribute&&a.removeAttribute(c.expando);delete f[d]}}}});c.fn.extend({data:function(a,b){if(typeof a==="undefined"&&this.length)return c.data(this[0]);else if(typeof a==="object")return this.each(function(){c.data(this,a)});var d=a.split(".");d[1]=d[1]?"."+d[1]:"";if(b===w){var f=this.triggerHandler("getData"+d[1]+"!",[d[0]]);if(f===w&&this.length)f=c.data(this[0],a);return f===w&&d[1]?this.data(d[0]):f}else return this.trigger("setData"+d[1]+"!",[d[0],b]).each(function(){c.data(this,
+a,b)})},removeData:function(a){return this.each(function(){c.removeData(this,a)})}});c.extend({queue:function(a,b,d){if(a){b=(b||"fx")+"queue";var f=c.data(a,b);if(!d)return f||[];if(!f||c.isArray(d))f=c.data(a,b,c.makeArray(d));else f.push(d);return f}},dequeue:function(a,b){b=b||"fx";var d=c.queue(a,b),f=d.shift();if(f==="inprogress")f=d.shift();if(f){b==="fx"&&d.unshift("inprogress");f.call(a,function(){c.dequeue(a,b)})}}});c.fn.extend({queue:function(a,b){if(typeof a!=="string"){b=a;a="fx"}if(b===
+w)return c.queue(this[0],a);return this.each(function(){var d=c.queue(this,a,b);a==="fx"&&d[0]!=="inprogress"&&c.dequeue(this,a)})},dequeue:function(a){return this.each(function(){c.dequeue(this,a)})},delay:function(a,b){a=c.fx?c.fx.speeds[a]||a:a;b=b||"fx";return this.queue(b,function(){var d=this;setTimeout(function(){c.dequeue(d,b)},a)})},clearQueue:function(a){return this.queue(a||"fx",[])}});var Aa=/[\n\t]/g,ca=/\s+/,Za=/\r/g,$a=/href|src|style/,ab=/(button|input)/i,bb=/(button|input|object|select|textarea)/i,
+cb=/^(a|area)$/i,Ba=/radio|checkbox/;c.fn.extend({attr:function(a,b){return X(this,a,b,true,c.attr)},removeAttr:function(a){return this.each(function(){c.attr(this,a,"");this.nodeType===1&&this.removeAttribute(a)})},addClass:function(a){if(c.isFunction(a))return this.each(function(n){var r=c(this);r.addClass(a.call(this,n,r.attr("class")))});if(a&&typeof a==="string")for(var b=(a||"").split(ca),d=0,f=this.length;d<f;d++){var e=this[d];if(e.nodeType===1)if(e.className){for(var j=" "+e.className+" ",
+i=e.className,o=0,k=b.length;o<k;o++)if(j.indexOf(" "+b[o]+" ")<0)i+=" "+b[o];e.className=c.trim(i)}else e.className=a}return this},removeClass:function(a){if(c.isFunction(a))return this.each(function(k){var n=c(this);n.removeClass(a.call(this,k,n.attr("class")))});if(a&&typeof a==="string"||a===w)for(var b=(a||"").split(ca),d=0,f=this.length;d<f;d++){var e=this[d];if(e.nodeType===1&&e.className)if(a){for(var j=(" "+e.className+" ").replace(Aa," "),i=0,o=b.length;i<o;i++)j=j.replace(" "+b[i]+" ",
+" ");e.className=c.trim(j)}else e.className=""}return this},toggleClass:function(a,b){var d=typeof a,f=typeof b==="boolean";if(c.isFunction(a))return this.each(function(e){var j=c(this);j.toggleClass(a.call(this,e,j.attr("class"),b),b)});return this.each(function(){if(d==="string")for(var e,j=0,i=c(this),o=b,k=a.split(ca);e=k[j++];){o=f?o:!i.hasClass(e);i[o?"addClass":"removeClass"](e)}else if(d==="undefined"||d==="boolean"){this.className&&c.data(this,"__className__",this.className);this.className=
+this.className||a===false?"":c.data(this,"__className__")||""}})},hasClass:function(a){a=" "+a+" ";for(var b=0,d=this.length;b<d;b++)if((" "+this[b].className+" ").replace(Aa," ").indexOf(a)>-1)return true;return false},val:function(a){if(a===w){var b=this[0];if(b){if(c.nodeName(b,"option"))return(b.attributes.value||{}).specified?b.value:b.text;if(c.nodeName(b,"select")){var d=b.selectedIndex,f=[],e=b.options;b=b.type==="select-one";if(d<0)return null;var j=b?d:0;for(d=b?d+1:e.length;j<d;j++){var i=
+e[j];if(i.selected){a=c(i).val();if(b)return a;f.push(a)}}return f}if(Ba.test(b.type)&&!c.support.checkOn)return b.getAttribute("value")===null?"on":b.value;return(b.value||"").replace(Za,"")}return w}var o=c.isFunction(a);return this.each(function(k){var n=c(this),r=a;if(this.nodeType===1){if(o)r=a.call(this,k,n.val());if(typeof r==="number")r+="";if(c.isArray(r)&&Ba.test(this.type))this.checked=c.inArray(n.val(),r)>=0;else if(c.nodeName(this,"select")){var u=c.makeArray(r);c("option",this).each(function(){this.selected=
+c.inArray(c(this).val(),u)>=0});if(!u.length)this.selectedIndex=-1}else this.value=r}})}});c.extend({attrFn:{val:true,css:true,html:true,text:true,data:true,width:true,height:true,offset:true},attr:function(a,b,d,f){if(!a||a.nodeType===3||a.nodeType===8)return w;if(f&&b in c.attrFn)return c(a)[b](d);f=a.nodeType!==1||!c.isXMLDoc(a);var e=d!==w;b=f&&c.props[b]||b;if(a.nodeType===1){var j=$a.test(b);if(b in a&&f&&!j){if(e){b==="type"&&ab.test(a.nodeName)&&a.parentNode&&c.error("type property can't be changed");
+a[b]=d}if(c.nodeName(a,"form")&&a.getAttributeNode(b))return a.getAttributeNode(b).nodeValue;if(b==="tabIndex")return(b=a.getAttributeNode("tabIndex"))&&b.specified?b.value:bb.test(a.nodeName)||cb.test(a.nodeName)&&a.href?0:w;return a[b]}if(!c.support.style&&f&&b==="style"){if(e)a.style.cssText=""+d;return a.style.cssText}e&&a.setAttribute(b,""+d);a=!c.support.hrefNormalized&&f&&j?a.getAttribute(b,2):a.getAttribute(b);return a===null?w:a}return c.style(a,b,d)}});var O=/\.(.*)$/,db=function(a){return a.replace(/[^\w\s\.\|`]/g,
+function(b){return"\\"+b})};c.event={add:function(a,b,d,f){if(!(a.nodeType===3||a.nodeType===8)){if(a.setInterval&&a!==A&&!a.frameElement)a=A;var e,j;if(d.handler){e=d;d=e.handler}if(!d.guid)d.guid=c.guid++;if(j=c.data(a)){var i=j.events=j.events||{},o=j.handle;if(!o)j.handle=o=function(){return typeof c!=="undefined"&&!c.event.triggered?c.event.handle.apply(o.elem,arguments):w};o.elem=a;b=b.split(" ");for(var k,n=0,r;k=b[n++];){j=e?c.extend({},e):{handler:d,data:f};if(k.indexOf(".")>-1){r=k.split(".");
+k=r.shift();j.namespace=r.slice(0).sort().join(".")}else{r=[];j.namespace=""}j.type=k;j.guid=d.guid;var u=i[k],z=c.event.special[k]||{};if(!u){u=i[k]=[];if(!z.setup||z.setup.call(a,f,r,o)===false)if(a.addEventListener)a.addEventListener(k,o,false);else a.attachEvent&&a.attachEvent("on"+k,o)}if(z.add){z.add.call(a,j);if(!j.handler.guid)j.handler.guid=d.guid}u.push(j);c.event.global[k]=true}a=null}}},global:{},remove:function(a,b,d,f){if(!(a.nodeType===3||a.nodeType===8)){var e,j=0,i,o,k,n,r,u,z=c.data(a),
+C=z&&z.events;if(z&&C){if(b&&b.type){d=b.handler;b=b.type}if(!b||typeof b==="string"&&b.charAt(0)==="."){b=b||"";for(e in C)c.event.remove(a,e+b)}else{for(b=b.split(" ");e=b[j++];){n=e;i=e.indexOf(".")<0;o=[];if(!i){o=e.split(".");e=o.shift();k=new RegExp("(^|\\.)"+c.map(o.slice(0).sort(),db).join("\\.(?:.*\\.)?")+"(\\.|$)")}if(r=C[e])if(d){n=c.event.special[e]||{};for(B=f||0;B<r.length;B++){u=r[B];if(d.guid===u.guid){if(i||k.test(u.namespace)){f==null&&r.splice(B--,1);n.remove&&n.remove.call(a,u)}if(f!=
+null)break}}if(r.length===0||f!=null&&r.length===1){if(!n.teardown||n.teardown.call(a,o)===false)Ca(a,e,z.handle);delete C[e]}}else for(var B=0;B<r.length;B++){u=r[B];if(i||k.test(u.namespace)){c.event.remove(a,n,u.handler,B);r.splice(B--,1)}}}if(c.isEmptyObject(C)){if(b=z.handle)b.elem=null;delete z.events;delete z.handle;c.isEmptyObject(z)&&c.removeData(a)}}}}},trigger:function(a,b,d,f){var e=a.type||a;if(!f){a=typeof a==="object"?a[G]?a:c.extend(c.Event(e),a):c.Event(e);if(e.indexOf("!")>=0){a.type=
+e=e.slice(0,-1);a.exclusive=true}if(!d){a.stopPropagation();c.event.global[e]&&c.each(c.cache,function(){this.events&&this.events[e]&&c.event.trigger(a,b,this.handle.elem)})}if(!d||d.nodeType===3||d.nodeType===8)return w;a.result=w;a.target=d;b=c.makeArray(b);b.unshift(a)}a.currentTarget=d;(f=c.data(d,"handle"))&&f.apply(d,b);f=d.parentNode||d.ownerDocument;try{if(!(d&&d.nodeName&&c.noData[d.nodeName.toLowerCase()]))if(d["on"+e]&&d["on"+e].apply(d,b)===false)a.result=false}catch(j){}if(!a.isPropagationStopped()&&
+f)c.event.trigger(a,b,f,true);else if(!a.isDefaultPrevented()){f=a.target;var i,o=c.nodeName(f,"a")&&e==="click",k=c.event.special[e]||{};if((!k._default||k._default.call(d,a)===false)&&!o&&!(f&&f.nodeName&&c.noData[f.nodeName.toLowerCase()])){try{if(f[e]){if(i=f["on"+e])f["on"+e]=null;c.event.triggered=true;f[e]()}}catch(n){}if(i)f["on"+e]=i;c.event.triggered=false}}},handle:function(a){var b,d,f,e;a=arguments[0]=c.event.fix(a||A.event);a.currentTarget=this;b=a.type.indexOf(".")<0&&!a.exclusive;
+if(!b){d=a.type.split(".");a.type=d.shift();f=new RegExp("(^|\\.)"+d.slice(0).sort().join("\\.(?:.*\\.)?")+"(\\.|$)")}e=c.data(this,"events");d=e[a.type];if(e&&d){d=d.slice(0);e=0;for(var j=d.length;e<j;e++){var i=d[e];if(b||f.test(i.namespace)){a.handler=i.handler;a.data=i.data;a.handleObj=i;i=i.handler.apply(this,arguments);if(i!==w){a.result=i;if(i===false){a.preventDefault();a.stopPropagation()}}if(a.isImmediatePropagationStopped())break}}}return a.result},props:"altKey attrChange attrName bubbles button cancelable charCode clientX clientY ctrlKey currentTarget data detail eventPhase fromElement handler keyCode layerX layerY metaKey newValue offsetX offsetY originalTarget pageX pageY prevValue relatedNode relatedTarget screenX screenY shiftKey srcElement target toElement view wheelDelta which".split(" "),
+fix:function(a){if(a[G])return a;var b=a;a=c.Event(b);for(var d=this.props.length,f;d;){f=this.props[--d];a[f]=b[f]}if(!a.target)a.target=a.srcElement||s;if(a.target.nodeType===3)a.target=a.target.parentNode;if(!a.relatedTarget&&a.fromElement)a.relatedTarget=a.fromElement===a.target?a.toElement:a.fromElement;if(a.pageX==null&&a.clientX!=null){b=s.documentElement;d=s.body;a.pageX=a.clientX+(b&&b.scrollLeft||d&&d.scrollLeft||0)-(b&&b.clientLeft||d&&d.clientLeft||0);a.pageY=a.clientY+(b&&b.scrollTop||
+d&&d.scrollTop||0)-(b&&b.clientTop||d&&d.clientTop||0)}if(!a.which&&(a.charCode||a.charCode===0?a.charCode:a.keyCode))a.which=a.charCode||a.keyCode;if(!a.metaKey&&a.ctrlKey)a.metaKey=a.ctrlKey;if(!a.which&&a.button!==w)a.which=a.button&1?1:a.button&2?3:a.button&4?2:0;return a},guid:1E8,proxy:c.proxy,special:{ready:{setup:c.bindReady,teardown:c.noop},live:{add:function(a){c.event.add(this,a.origType,c.extend({},a,{handler:oa}))},remove:function(a){var b=true,d=a.origType.replace(O,"");c.each(c.data(this,
+"events").live||[],function(){if(d===this.origType.replace(O,""))return b=false});b&&c.event.remove(this,a.origType,oa)}},beforeunload:{setup:function(a,b,d){if(this.setInterval)this.onbeforeunload=d;return false},teardown:function(a,b){if(this.onbeforeunload===b)this.onbeforeunload=null}}}};var Ca=s.removeEventListener?function(a,b,d){a.removeEventListener(b,d,false)}:function(a,b,d){a.detachEvent("on"+b,d)};c.Event=function(a){if(!this.preventDefault)return new c.Event(a);if(a&&a.type){this.originalEvent=
+a;this.type=a.type}else this.type=a;this.timeStamp=J();this[G]=true};c.Event.prototype={preventDefault:function(){this.isDefaultPrevented=Z;var a=this.originalEvent;if(a){a.preventDefault&&a.preventDefault();a.returnValue=false}},stopPropagation:function(){this.isPropagationStopped=Z;var a=this.originalEvent;if(a){a.stopPropagation&&a.stopPropagation();a.cancelBubble=true}},stopImmediatePropagation:function(){this.isImmediatePropagationStopped=Z;this.stopPropagation()},isDefaultPrevented:Y,isPropagationStopped:Y,
+isImmediatePropagationStopped:Y};var Da=function(a){var b=a.relatedTarget;try{for(;b&&b!==this;)b=b.parentNode;if(b!==this){a.type=a.data;c.event.handle.apply(this,arguments)}}catch(d){}},Ea=function(a){a.type=a.data;c.event.handle.apply(this,arguments)};c.each({mouseenter:"mouseover",mouseleave:"mouseout"},function(a,b){c.event.special[a]={setup:function(d){c.event.add(this,b,d&&d.selector?Ea:Da,a)},teardown:function(d){c.event.remove(this,b,d&&d.selector?Ea:Da)}}});if(!c.support.submitBubbles)c.event.special.submit=
+{setup:function(){if(this.nodeName.toLowerCase()!=="form"){c.event.add(this,"click.specialSubmit",function(a){var b=a.target,d=b.type;if((d==="submit"||d==="image")&&c(b).closest("form").length)return na("submit",this,arguments)});c.event.add(this,"keypress.specialSubmit",function(a){var b=a.target,d=b.type;if((d==="text"||d==="password")&&c(b).closest("form").length&&a.keyCode===13)return na("submit",this,arguments)})}else return false},teardown:function(){c.event.remove(this,".specialSubmit")}};
+if(!c.support.changeBubbles){var da=/textarea|input|select/i,ea,Fa=function(a){var b=a.type,d=a.value;if(b==="radio"||b==="checkbox")d=a.checked;else if(b==="select-multiple")d=a.selectedIndex>-1?c.map(a.options,function(f){return f.selected}).join("-"):"";else if(a.nodeName.toLowerCase()==="select")d=a.selectedIndex;return d},fa=function(a,b){var d=a.target,f,e;if(!(!da.test(d.nodeName)||d.readOnly)){f=c.data(d,"_change_data");e=Fa(d);if(a.type!=="focusout"||d.type!=="radio")c.data(d,"_change_data",
+e);if(!(f===w||e===f))if(f!=null||e){a.type="change";return c.event.trigger(a,b,d)}}};c.event.special.change={filters:{focusout:fa,click:function(a){var b=a.target,d=b.type;if(d==="radio"||d==="checkbox"||b.nodeName.toLowerCase()==="select")return fa.call(this,a)},keydown:function(a){var b=a.target,d=b.type;if(a.keyCode===13&&b.nodeName.toLowerCase()!=="textarea"||a.keyCode===32&&(d==="checkbox"||d==="radio")||d==="select-multiple")return fa.call(this,a)},beforeactivate:function(a){a=a.target;c.data(a,
+"_change_data",Fa(a))}},setup:function(){if(this.type==="file")return false;for(var a in ea)c.event.add(this,a+".specialChange",ea[a]);return da.test(this.nodeName)},teardown:function(){c.event.remove(this,".specialChange");return da.test(this.nodeName)}};ea=c.event.special.change.filters}s.addEventListener&&c.each({focus:"focusin",blur:"focusout"},function(a,b){function d(f){f=c.event.fix(f);f.type=b;return c.event.handle.call(this,f)}c.event.special[b]={setup:function(){this.addEventListener(a,
+d,true)},teardown:function(){this.removeEventListener(a,d,true)}}});c.each(["bind","one"],function(a,b){c.fn[b]=function(d,f,e){if(typeof d==="object"){for(var j in d)this[b](j,f,d[j],e);return this}if(c.isFunction(f)){e=f;f=w}var i=b==="one"?c.proxy(e,function(k){c(this).unbind(k,i);return e.apply(this,arguments)}):e;if(d==="unload"&&b!=="one")this.one(d,f,e);else{j=0;for(var o=this.length;j<o;j++)c.event.add(this[j],d,i,f)}return this}});c.fn.extend({unbind:function(a,b){if(typeof a==="object"&&
+!a.preventDefault)for(var d in a)this.unbind(d,a[d]);else{d=0;for(var f=this.length;d<f;d++)c.event.remove(this[d],a,b)}return this},delegate:function(a,b,d,f){return this.live(b,d,f,a)},undelegate:function(a,b,d){return arguments.length===0?this.unbind("live"):this.die(b,null,d,a)},trigger:function(a,b){return this.each(function(){c.event.trigger(a,b,this)})},triggerHandler:function(a,b){if(this[0]){a=c.Event(a);a.preventDefault();a.stopPropagation();c.event.trigger(a,b,this[0]);return a.result}},
+toggle:function(a){for(var b=arguments,d=1;d<b.length;)c.proxy(a,b[d++]);return this.click(c.proxy(a,function(f){var e=(c.data(this,"lastToggle"+a.guid)||0)%d;c.data(this,"lastToggle"+a.guid,e+1);f.preventDefault();return b[e].apply(this,arguments)||false}))},hover:function(a,b){return this.mouseenter(a).mouseleave(b||a)}});var Ga={focus:"focusin",blur:"focusout",mouseenter:"mouseover",mouseleave:"mouseout"};c.each(["live","die"],function(a,b){c.fn[b]=function(d,f,e,j){var i,o=0,k,n,r=j||this.selector,
+u=j?this:c(this.context);if(c.isFunction(f)){e=f;f=w}for(d=(d||"").split(" ");(i=d[o++])!=null;){j=O.exec(i);k="";if(j){k=j[0];i=i.replace(O,"")}if(i==="hover")d.push("mouseenter"+k,"mouseleave"+k);else{n=i;if(i==="focus"||i==="blur"){d.push(Ga[i]+k);i+=k}else i=(Ga[i]||i)+k;b==="live"?u.each(function(){c.event.add(this,pa(i,r),{data:f,selector:r,handler:e,origType:i,origHandler:e,preType:n})}):u.unbind(pa(i,r),e)}}return this}});c.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".split(" "),
+function(a,b){c.fn[b]=function(d){return d?this.bind(b,d):this.trigger(b)};if(c.attrFn)c.attrFn[b]=true});A.attachEvent&&!A.addEventListener&&A.attachEvent("onunload",function(){for(var a in c.cache)if(c.cache[a].handle)try{c.event.remove(c.cache[a].handle.elem)}catch(b){}});(function(){function a(g){for(var h="",l,m=0;g[m];m++){l=g[m];if(l.nodeType===3||l.nodeType===4)h+=l.nodeValue;else if(l.nodeType!==8)h+=a(l.childNodes)}return h}function b(g,h,l,m,q,p){q=0;for(var v=m.length;q<v;q++){var t=m[q];
+if(t){t=t[g];for(var y=false;t;){if(t.sizcache===l){y=m[t.sizset];break}if(t.nodeType===1&&!p){t.sizcache=l;t.sizset=q}if(t.nodeName.toLowerCase()===h){y=t;break}t=t[g]}m[q]=y}}}function d(g,h,l,m,q,p){q=0;for(var v=m.length;q<v;q++){var t=m[q];if(t){t=t[g];for(var y=false;t;){if(t.sizcache===l){y=m[t.sizset];break}if(t.nodeType===1){if(!p){t.sizcache=l;t.sizset=q}if(typeof h!=="string"){if(t===h){y=true;break}}else if(k.filter(h,[t]).length>0){y=t;break}}t=t[g]}m[q]=y}}}var f=/((?:\((?:\([^()]+\)|[^()]+)+\)|\[(?:\[[^[\]]*\]|['"][^'"]*['"]|[^[\]'"]+)+\]|\\.|[^ >+~,(\[\\]+)+|[>+~])(\s*,\s*)?((?:.|\r|\n)*)/g,
+e=0,j=Object.prototype.toString,i=false,o=true;[0,0].sort(function(){o=false;return 0});var k=function(g,h,l,m){l=l||[];var q=h=h||s;if(h.nodeType!==1&&h.nodeType!==9)return[];if(!g||typeof g!=="string")return l;for(var p=[],v,t,y,S,H=true,M=x(h),I=g;(f.exec(""),v=f.exec(I))!==null;){I=v[3];p.push(v[1]);if(v[2]){S=v[3];break}}if(p.length>1&&r.exec(g))if(p.length===2&&n.relative[p[0]])t=ga(p[0]+p[1],h);else for(t=n.relative[p[0]]?[h]:k(p.shift(),h);p.length;){g=p.shift();if(n.relative[g])g+=p.shift();
+t=ga(g,t)}else{if(!m&&p.length>1&&h.nodeType===9&&!M&&n.match.ID.test(p[0])&&!n.match.ID.test(p[p.length-1])){v=k.find(p.shift(),h,M);h=v.expr?k.filter(v.expr,v.set)[0]:v.set[0]}if(h){v=m?{expr:p.pop(),set:z(m)}:k.find(p.pop(),p.length===1&&(p[0]==="~"||p[0]==="+")&&h.parentNode?h.parentNode:h,M);t=v.expr?k.filter(v.expr,v.set):v.set;if(p.length>0)y=z(t);else H=false;for(;p.length;){var D=p.pop();v=D;if(n.relative[D])v=p.pop();else D="";if(v==null)v=h;n.relative[D](y,v,M)}}else y=[]}y||(y=t);y||k.error(D||
+g);if(j.call(y)==="[object Array]")if(H)if(h&&h.nodeType===1)for(g=0;y[g]!=null;g++){if(y[g]&&(y[g]===true||y[g].nodeType===1&&E(h,y[g])))l.push(t[g])}else for(g=0;y[g]!=null;g++)y[g]&&y[g].nodeType===1&&l.push(t[g]);else l.push.apply(l,y);else z(y,l);if(S){k(S,q,l,m);k.uniqueSort(l)}return l};k.uniqueSort=function(g){if(B){i=o;g.sort(B);if(i)for(var h=1;h<g.length;h++)g[h]===g[h-1]&&g.splice(h--,1)}return g};k.matches=function(g,h){return k(g,null,null,h)};k.find=function(g,h,l){var m,q;if(!g)return[];
+for(var p=0,v=n.order.length;p<v;p++){var t=n.order[p];if(q=n.leftMatch[t].exec(g)){var y=q[1];q.splice(1,1);if(y.substr(y.length-1)!=="\\"){q[1]=(q[1]||"").replace(/\\/g,"");m=n.find[t](q,h,l);if(m!=null){g=g.replace(n.match[t],"");break}}}}m||(m=h.getElementsByTagName("*"));return{set:m,expr:g}};k.filter=function(g,h,l,m){for(var q=g,p=[],v=h,t,y,S=h&&h[0]&&x(h[0]);g&&h.length;){for(var H in n.filter)if((t=n.leftMatch[H].exec(g))!=null&&t[2]){var M=n.filter[H],I,D;D=t[1];y=false;t.splice(1,1);if(D.substr(D.length-
+1)!=="\\"){if(v===p)p=[];if(n.preFilter[H])if(t=n.preFilter[H](t,v,l,p,m,S)){if(t===true)continue}else y=I=true;if(t)for(var U=0;(D=v[U])!=null;U++)if(D){I=M(D,t,U,v);var Ha=m^!!I;if(l&&I!=null)if(Ha)y=true;else v[U]=false;else if(Ha){p.push(D);y=true}}if(I!==w){l||(v=p);g=g.replace(n.match[H],"");if(!y)return[];break}}}if(g===q)if(y==null)k.error(g);else break;q=g}return v};k.error=function(g){throw"Syntax error, unrecognized expression: "+g;};var n=k.selectors={order:["ID","NAME","TAG"],match:{ID:/#((?:[\w\u00c0-\uFFFF-]|\\.)+)/,
+CLASS:/\.((?:[\w\u00c0-\uFFFF-]|\\.)+)/,NAME:/\[name=['"]*((?:[\w\u00c0-\uFFFF-]|\\.)+)['"]*\]/,ATTR:/\[\s*((?:[\w\u00c0-\uFFFF-]|\\.)+)\s*(?:(\S?=)\s*(['"]*)(.*?)\3|)\s*\]/,TAG:/^((?:[\w\u00c0-\uFFFF\*-]|\\.)+)/,CHILD:/:(only|nth|last|first)-child(?:\((even|odd|[\dn+-]*)\))?/,POS:/:(nth|eq|gt|lt|first|last|even|odd)(?:\((\d*)\))?(?=[^-]|$)/,PSEUDO:/:((?:[\w\u00c0-\uFFFF-]|\\.)+)(?:\((['"]?)((?:\([^\)]+\)|[^\(\)]*)+)\2\))?/},leftMatch:{},attrMap:{"class":"className","for":"htmlFor"},attrHandle:{href:function(g){return g.getAttribute("href")}},
+relative:{"+":function(g,h){var l=typeof h==="string",m=l&&!/\W/.test(h);l=l&&!m;if(m)h=h.toLowerCase();m=0;for(var q=g.length,p;m<q;m++)if(p=g[m]){for(;(p=p.previousSibling)&&p.nodeType!==1;);g[m]=l||p&&p.nodeName.toLowerCase()===h?p||false:p===h}l&&k.filter(h,g,true)},">":function(g,h){var l=typeof h==="string";if(l&&!/\W/.test(h)){h=h.toLowerCase();for(var m=0,q=g.length;m<q;m++){var p=g[m];if(p){l=p.parentNode;g[m]=l.nodeName.toLowerCase()===h?l:false}}}else{m=0;for(q=g.length;m<q;m++)if(p=g[m])g[m]=
+l?p.parentNode:p.parentNode===h;l&&k.filter(h,g,true)}},"":function(g,h,l){var m=e++,q=d;if(typeof h==="string"&&!/\W/.test(h)){var p=h=h.toLowerCase();q=b}q("parentNode",h,m,g,p,l)},"~":function(g,h,l){var m=e++,q=d;if(typeof h==="string"&&!/\W/.test(h)){var p=h=h.toLowerCase();q=b}q("previousSibling",h,m,g,p,l)}},find:{ID:function(g,h,l){if(typeof h.getElementById!=="undefined"&&!l)return(g=h.getElementById(g[1]))?[g]:[]},NAME:function(g,h){if(typeof h.getElementsByName!=="undefined"){var l=[];
+h=h.getElementsByName(g[1]);for(var m=0,q=h.length;m<q;m++)h[m].getAttribute("name")===g[1]&&l.push(h[m]);return l.length===0?null:l}},TAG:function(g,h){return h.getElementsByTagName(g[1])}},preFilter:{CLASS:function(g,h,l,m,q,p){g=" "+g[1].replace(/\\/g,"")+" ";if(p)return g;p=0;for(var v;(v=h[p])!=null;p++)if(v)if(q^(v.className&&(" "+v.className+" ").replace(/[\t\n]/g," ").indexOf(g)>=0))l||m.push(v);else if(l)h[p]=false;return false},ID:function(g){return g[1].replace(/\\/g,"")},TAG:function(g){return g[1].toLowerCase()},
+CHILD:function(g){if(g[1]==="nth"){var h=/(-?)(\d*)n((?:\+|-)?\d*)/.exec(g[2]==="even"&&"2n"||g[2]==="odd"&&"2n+1"||!/\D/.test(g[2])&&"0n+"+g[2]||g[2]);g[2]=h[1]+(h[2]||1)-0;g[3]=h[3]-0}g[0]=e++;return g},ATTR:function(g,h,l,m,q,p){h=g[1].replace(/\\/g,"");if(!p&&n.attrMap[h])g[1]=n.attrMap[h];if(g[2]==="~=")g[4]=" "+g[4]+" ";return g},PSEUDO:function(g,h,l,m,q){if(g[1]==="not")if((f.exec(g[3])||"").length>1||/^\w/.test(g[3]))g[3]=k(g[3],null,null,h);else{g=k.filter(g[3],h,l,true^q);l||m.push.apply(m,
+g);return false}else if(n.match.POS.test(g[0])||n.match.CHILD.test(g[0]))return true;return g},POS:function(g){g.unshift(true);return g}},filters:{enabled:function(g){return g.disabled===false&&g.type!=="hidden"},disabled:function(g){return g.disabled===true},checked:function(g){return g.checked===true},selected:function(g){return g.selected===true},parent:function(g){return!!g.firstChild},empty:function(g){return!g.firstChild},has:function(g,h,l){return!!k(l[3],g).length},header:function(g){return/h\d/i.test(g.nodeName)},
+text:function(g){return"text"===g.type},radio:function(g){return"radio"===g.type},checkbox:function(g){return"checkbox"===g.type},file:function(g){return"file"===g.type},password:function(g){return"password"===g.type},submit:function(g){return"submit"===g.type},image:function(g){return"image"===g.type},reset:function(g){return"reset"===g.type},button:function(g){return"button"===g.type||g.nodeName.toLowerCase()==="button"},input:function(g){return/input|select|textarea|button/i.test(g.nodeName)}},
+setFilters:{first:function(g,h){return h===0},last:function(g,h,l,m){return h===m.length-1},even:function(g,h){return h%2===0},odd:function(g,h){return h%2===1},lt:function(g,h,l){return h<l[3]-0},gt:function(g,h,l){return h>l[3]-0},nth:function(g,h,l){return l[3]-0===h},eq:function(g,h,l){return l[3]-0===h}},filter:{PSEUDO:function(g,h,l,m){var q=h[1],p=n.filters[q];if(p)return p(g,l,h,m);else if(q==="contains")return(g.textContent||g.innerText||a([g])||"").indexOf(h[3])>=0;else if(q==="not"){h=
+h[3];l=0;for(m=h.length;l<m;l++)if(h[l]===g)return false;return true}else k.error("Syntax error, unrecognized expression: "+q)},CHILD:function(g,h){var l=h[1],m=g;switch(l){case "only":case "first":for(;m=m.previousSibling;)if(m.nodeType===1)return false;if(l==="first")return true;m=g;case "last":for(;m=m.nextSibling;)if(m.nodeType===1)return false;return true;case "nth":l=h[2];var q=h[3];if(l===1&&q===0)return true;h=h[0];var p=g.parentNode;if(p&&(p.sizcache!==h||!g.nodeIndex)){var v=0;for(m=p.firstChild;m;m=
+m.nextSibling)if(m.nodeType===1)m.nodeIndex=++v;p.sizcache=h}g=g.nodeIndex-q;return l===0?g===0:g%l===0&&g/l>=0}},ID:function(g,h){return g.nodeType===1&&g.getAttribute("id")===h},TAG:function(g,h){return h==="*"&&g.nodeType===1||g.nodeName.toLowerCase()===h},CLASS:function(g,h){return(" "+(g.className||g.getAttribute("class"))+" ").indexOf(h)>-1},ATTR:function(g,h){var l=h[1];g=n.attrHandle[l]?n.attrHandle[l](g):g[l]!=null?g[l]:g.getAttribute(l);l=g+"";var m=h[2];h=h[4];return g==null?m==="!=":m===
+"="?l===h:m==="*="?l.indexOf(h)>=0:m==="~="?(" "+l+" ").indexOf(h)>=0:!h?l&&g!==false:m==="!="?l!==h:m==="^="?l.indexOf(h)===0:m==="$="?l.substr(l.length-h.length)===h:m==="|="?l===h||l.substr(0,h.length+1)===h+"-":false},POS:function(g,h,l,m){var q=n.setFilters[h[2]];if(q)return q(g,l,h,m)}}},r=n.match.POS;for(var u in n.match){n.match[u]=new RegExp(n.match[u].source+/(?![^\[]*\])(?![^\(]*\))/.source);n.leftMatch[u]=new RegExp(/(^(?:.|\r|\n)*?)/.source+n.match[u].source.replace(/\\(\d+)/g,function(g,
+h){return"\\"+(h-0+1)}))}var z=function(g,h){g=Array.prototype.slice.call(g,0);if(h){h.push.apply(h,g);return h}return g};try{Array.prototype.slice.call(s.documentElement.childNodes,0)}catch(C){z=function(g,h){h=h||[];if(j.call(g)==="[object Array]")Array.prototype.push.apply(h,g);else if(typeof g.length==="number")for(var l=0,m=g.length;l<m;l++)h.push(g[l]);else for(l=0;g[l];l++)h.push(g[l]);return h}}var B;if(s.documentElement.compareDocumentPosition)B=function(g,h){if(!g.compareDocumentPosition||
+!h.compareDocumentPosition){if(g==h)i=true;return g.compareDocumentPosition?-1:1}g=g.compareDocumentPosition(h)&4?-1:g===h?0:1;if(g===0)i=true;return g};else if("sourceIndex"in s.documentElement)B=function(g,h){if(!g.sourceIndex||!h.sourceIndex){if(g==h)i=true;return g.sourceIndex?-1:1}g=g.sourceIndex-h.sourceIndex;if(g===0)i=true;return g};else if(s.createRange)B=function(g,h){if(!g.ownerDocument||!h.ownerDocument){if(g==h)i=true;return g.ownerDocument?-1:1}var l=g.ownerDocument.createRange(),m=
+h.ownerDocument.createRange();l.setStart(g,0);l.setEnd(g,0);m.setStart(h,0);m.setEnd(h,0);g=l.compareBoundaryPoints(Range.START_TO_END,m);if(g===0)i=true;return g};(function(){var g=s.createElement("div"),h="script"+(new Date).getTime();g.innerHTML="<a name='"+h+"'/>";var l=s.documentElement;l.insertBefore(g,l.firstChild);if(s.getElementById(h)){n.find.ID=function(m,q,p){if(typeof q.getElementById!=="undefined"&&!p)return(q=q.getElementById(m[1]))?q.id===m[1]||typeof q.getAttributeNode!=="undefined"&&
+q.getAttributeNode("id").nodeValue===m[1]?[q]:w:[]};n.filter.ID=function(m,q){var p=typeof m.getAttributeNode!=="undefined"&&m.getAttributeNode("id");return m.nodeType===1&&p&&p.nodeValue===q}}l.removeChild(g);l=g=null})();(function(){var g=s.createElement("div");g.appendChild(s.createComment(""));if(g.getElementsByTagName("*").length>0)n.find.TAG=function(h,l){l=l.getElementsByTagName(h[1]);if(h[1]==="*"){h=[];for(var m=0;l[m];m++)l[m].nodeType===1&&h.push(l[m]);l=h}return l};g.innerHTML="<a href='#'></a>";
+if(g.firstChild&&typeof g.firstChild.getAttribute!=="undefined"&&g.firstChild.getAttribute("href")!=="#")n.attrHandle.href=function(h){return h.getAttribute("href",2)};g=null})();s.querySelectorAll&&function(){var g=k,h=s.createElement("div");h.innerHTML="<p class='TEST'></p>";if(!(h.querySelectorAll&&h.querySelectorAll(".TEST").length===0)){k=function(m,q,p,v){q=q||s;if(!v&&q.nodeType===9&&!x(q))try{return z(q.querySelectorAll(m),p)}catch(t){}return g(m,q,p,v)};for(var l in g)k[l]=g[l];h=null}}();
+(function(){var g=s.createElement("div");g.innerHTML="<div class='test e'></div><div class='test'></div>";if(!(!g.getElementsByClassName||g.getElementsByClassName("e").length===0)){g.lastChild.className="e";if(g.getElementsByClassName("e").length!==1){n.order.splice(1,0,"CLASS");n.find.CLASS=function(h,l,m){if(typeof l.getElementsByClassName!=="undefined"&&!m)return l.getElementsByClassName(h[1])};g=null}}})();var E=s.compareDocumentPosition?function(g,h){return!!(g.compareDocumentPosition(h)&16)}:
+function(g,h){return g!==h&&(g.contains?g.contains(h):true)},x=function(g){return(g=(g?g.ownerDocument||g:0).documentElement)?g.nodeName!=="HTML":false},ga=function(g,h){var l=[],m="",q;for(h=h.nodeType?[h]:h;q=n.match.PSEUDO.exec(g);){m+=q[0];g=g.replace(n.match.PSEUDO,"")}g=n.relative[g]?g+"*":g;q=0;for(var p=h.length;q<p;q++)k(g,h[q],l);return k.filter(m,l)};c.find=k;c.expr=k.selectors;c.expr[":"]=c.expr.filters;c.unique=k.uniqueSort;c.text=a;c.isXMLDoc=x;c.contains=E})();var eb=/Until$/,fb=/^(?:parents|prevUntil|prevAll)/,
+gb=/,/;R=Array.prototype.slice;var Ia=function(a,b,d){if(c.isFunction(b))return c.grep(a,function(e,j){return!!b.call(e,j,e)===d});else if(b.nodeType)return c.grep(a,function(e){return e===b===d});else if(typeof b==="string"){var f=c.grep(a,function(e){return e.nodeType===1});if(Ua.test(b))return c.filter(b,f,!d);else b=c.filter(b,f)}return c.grep(a,function(e){return c.inArray(e,b)>=0===d})};c.fn.extend({find:function(a){for(var b=this.pushStack("","find",a),d=0,f=0,e=this.length;f<e;f++){d=b.length;
+c.find(a,this[f],b);if(f>0)for(var j=d;j<b.length;j++)for(var i=0;i<d;i++)if(b[i]===b[j]){b.splice(j--,1);break}}return b},has:function(a){var b=c(a);return this.filter(function(){for(var d=0,f=b.length;d<f;d++)if(c.contains(this,b[d]))return true})},not:function(a){return this.pushStack(Ia(this,a,false),"not",a)},filter:function(a){return this.pushStack(Ia(this,a,true),"filter",a)},is:function(a){return!!a&&c.filter(a,this).length>0},closest:function(a,b){if(c.isArray(a)){var d=[],f=this[0],e,j=
+{},i;if(f&&a.length){e=0;for(var o=a.length;e<o;e++){i=a[e];j[i]||(j[i]=c.expr.match.POS.test(i)?c(i,b||this.context):i)}for(;f&&f.ownerDocument&&f!==b;){for(i in j){e=j[i];if(e.jquery?e.index(f)>-1:c(f).is(e)){d.push({selector:i,elem:f});delete j[i]}}f=f.parentNode}}return d}var k=c.expr.match.POS.test(a)?c(a,b||this.context):null;return this.map(function(n,r){for(;r&&r.ownerDocument&&r!==b;){if(k?k.index(r)>-1:c(r).is(a))return r;r=r.parentNode}return null})},index:function(a){if(!a||typeof a===
+"string")return c.inArray(this[0],a?c(a):this.parent().children());return c.inArray(a.jquery?a[0]:a,this)},add:function(a,b){a=typeof a==="string"?c(a,b||this.context):c.makeArray(a);b=c.merge(this.get(),a);return this.pushStack(qa(a[0])||qa(b[0])?b:c.unique(b))},andSelf:function(){return this.add(this.prevObject)}});c.each({parent:function(a){return(a=a.parentNode)&&a.nodeType!==11?a:null},parents:function(a){return c.dir(a,"parentNode")},parentsUntil:function(a,b,d){return c.dir(a,"parentNode",
+d)},next:function(a){return c.nth(a,2,"nextSibling")},prev:function(a){return c.nth(a,2,"previousSibling")},nextAll:function(a){return c.dir(a,"nextSibling")},prevAll:function(a){return c.dir(a,"previousSibling")},nextUntil:function(a,b,d){return c.dir(a,"nextSibling",d)},prevUntil:function(a,b,d){return c.dir(a,"previousSibling",d)},siblings:function(a){return c.sibling(a.parentNode.firstChild,a)},children:function(a){return c.sibling(a.firstChild)},contents:function(a){return c.nodeName(a,"iframe")?
+a.contentDocument||a.contentWindow.document:c.makeArray(a.childNodes)}},function(a,b){c.fn[a]=function(d,f){var e=c.map(this,b,d);eb.test(a)||(f=d);if(f&&typeof f==="string")e=c.filter(f,e);e=this.length>1?c.unique(e):e;if((this.length>1||gb.test(f))&&fb.test(a))e=e.reverse();return this.pushStack(e,a,R.call(arguments).join(","))}});c.extend({filter:function(a,b,d){if(d)a=":not("+a+")";return c.find.matches(a,b)},dir:function(a,b,d){var f=[];for(a=a[b];a&&a.nodeType!==9&&(d===w||a.nodeType!==1||!c(a).is(d));){a.nodeType===
+1&&f.push(a);a=a[b]}return f},nth:function(a,b,d){b=b||1;for(var f=0;a;a=a[d])if(a.nodeType===1&&++f===b)break;return a},sibling:function(a,b){for(var d=[];a;a=a.nextSibling)a.nodeType===1&&a!==b&&d.push(a);return d}});var Ja=/ jQuery\d+="(?:\d+|null)"/g,V=/^\s+/,Ka=/(<([\w:]+)[^>]*?)\/>/g,hb=/^(?:area|br|col|embed|hr|img|input|link|meta|param)$/i,La=/<([\w:]+)/,ib=/<tbody/i,jb=/<|&#?\w+;/,ta=/<script|<object|<embed|<option|<style/i,ua=/checked\s*(?:[^=]|=\s*.checked.)/i,Ma=function(a,b,d){return hb.test(d)?
+a:b+"></"+d+">"},F={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,"",""]};F.optgroup=F.option;F.tbody=F.tfoot=F.colgroup=F.caption=F.thead;F.th=F.td;if(!c.support.htmlSerialize)F._default=[1,"div<div>","</div>"];c.fn.extend({text:function(a){if(c.isFunction(a))return this.each(function(b){var d=
+c(this);d.text(a.call(this,b,d.text()))});if(typeof a!=="object"&&a!==w)return this.empty().append((this[0]&&this[0].ownerDocument||s).createTextNode(a));return c.text(this)},wrapAll:function(a){if(c.isFunction(a))return this.each(function(d){c(this).wrapAll(a.call(this,d))});if(this[0]){var b=c(a,this[0].ownerDocument).eq(0).clone(true);this[0].parentNode&&b.insertBefore(this[0]);b.map(function(){for(var d=this;d.firstChild&&d.firstChild.nodeType===1;)d=d.firstChild;return d}).append(this)}return this},
+wrapInner:function(a){if(c.isFunction(a))return this.each(function(b){c(this).wrapInner(a.call(this,b))});return this.each(function(){var b=c(this),d=b.contents();d.length?d.wrapAll(a):b.append(a)})},wrap:function(a){return this.each(function(){c(this).wrapAll(a)})},unwrap:function(){return this.parent().each(function(){c.nodeName(this,"body")||c(this).replaceWith(this.childNodes)}).end()},append:function(){return this.domManip(arguments,true,function(a){this.nodeType===1&&this.appendChild(a)})},
+prepend:function(){return this.domManip(arguments,true,function(a){this.nodeType===1&&this.insertBefore(a,this.firstChild)})},before:function(){if(this[0]&&this[0].parentNode)return this.domManip(arguments,false,function(b){this.parentNode.insertBefore(b,this)});else if(arguments.length){var a=c(arguments[0]);a.push.apply(a,this.toArray());return this.pushStack(a,"before",arguments)}},after:function(){if(this[0]&&this[0].parentNode)return this.domManip(arguments,false,function(b){this.parentNode.insertBefore(b,
+this.nextSibling)});else if(arguments.length){var a=this.pushStack(this,"after",arguments);a.push.apply(a,c(arguments[0]).toArray());return a}},remove:function(a,b){for(var d=0,f;(f=this[d])!=null;d++)if(!a||c.filter(a,[f]).length){if(!b&&f.nodeType===1){c.cleanData(f.getElementsByTagName("*"));c.cleanData([f])}f.parentNode&&f.parentNode.removeChild(f)}return this},empty:function(){for(var a=0,b;(b=this[a])!=null;a++)for(b.nodeType===1&&c.cleanData(b.getElementsByTagName("*"));b.firstChild;)b.removeChild(b.firstChild);
+return this},clone:function(a){var b=this.map(function(){if(!c.support.noCloneEvent&&!c.isXMLDoc(this)){var d=this.outerHTML,f=this.ownerDocument;if(!d){d=f.createElement("div");d.appendChild(this.cloneNode(true));d=d.innerHTML}return c.clean([d.replace(Ja,"").replace(/=([^="'>\s]+\/)>/g,'="$1">').replace(V,"")],f)[0]}else return this.cloneNode(true)});if(a===true){ra(this,b);ra(this.find("*"),b.find("*"))}return b},html:function(a){if(a===w)return this[0]&&this[0].nodeType===1?this[0].innerHTML.replace(Ja,
+""):null;else if(typeof a==="string"&&!ta.test(a)&&(c.support.leadingWhitespace||!V.test(a))&&!F[(La.exec(a)||["",""])[1].toLowerCase()]){a=a.replace(Ka,Ma);try{for(var b=0,d=this.length;b<d;b++)if(this[b].nodeType===1){c.cleanData(this[b].getElementsByTagName("*"));this[b].innerHTML=a}}catch(f){this.empty().append(a)}}else c.isFunction(a)?this.each(function(e){var j=c(this),i=j.html();j.empty().append(function(){return a.call(this,e,i)})}):this.empty().append(a);return this},replaceWith:function(a){if(this[0]&&
+this[0].parentNode){if(c.isFunction(a))return this.each(function(b){var d=c(this),f=d.html();d.replaceWith(a.call(this,b,f))});if(typeof a!=="string")a=c(a).detach();return this.each(function(){var b=this.nextSibling,d=this.parentNode;c(this).remove();b?c(b).before(a):c(d).append(a)})}else return this.pushStack(c(c.isFunction(a)?a():a),"replaceWith",a)},detach:function(a){return this.remove(a,true)},domManip:function(a,b,d){function f(u){return c.nodeName(u,"table")?u.getElementsByTagName("tbody")[0]||
+u.appendChild(u.ownerDocument.createElement("tbody")):u}var e,j,i=a[0],o=[],k;if(!c.support.checkClone&&arguments.length===3&&typeof i==="string"&&ua.test(i))return this.each(function(){c(this).domManip(a,b,d,true)});if(c.isFunction(i))return this.each(function(u){var z=c(this);a[0]=i.call(this,u,b?z.html():w);z.domManip(a,b,d)});if(this[0]){e=i&&i.parentNode;e=c.support.parentNode&&e&&e.nodeType===11&&e.childNodes.length===this.length?{fragment:e}:sa(a,this,o);k=e.fragment;if(j=k.childNodes.length===
+1?(k=k.firstChild):k.firstChild){b=b&&c.nodeName(j,"tr");for(var n=0,r=this.length;n<r;n++)d.call(b?f(this[n],j):this[n],n>0||e.cacheable||this.length>1?k.cloneNode(true):k)}o.length&&c.each(o,Qa)}return this}});c.fragments={};c.each({appendTo:"append",prependTo:"prepend",insertBefore:"before",insertAfter:"after",replaceAll:"replaceWith"},function(a,b){c.fn[a]=function(d){var f=[];d=c(d);var e=this.length===1&&this[0].parentNode;if(e&&e.nodeType===11&&e.childNodes.length===1&&d.length===1){d[b](this[0]);
+return this}else{e=0;for(var j=d.length;e<j;e++){var i=(e>0?this.clone(true):this).get();c.fn[b].apply(c(d[e]),i);f=f.concat(i)}return this.pushStack(f,a,d.selector)}}});c.extend({clean:function(a,b,d,f){b=b||s;if(typeof b.createElement==="undefined")b=b.ownerDocument||b[0]&&b[0].ownerDocument||s;for(var e=[],j=0,i;(i=a[j])!=null;j++){if(typeof i==="number")i+="";if(i){if(typeof i==="string"&&!jb.test(i))i=b.createTextNode(i);else if(typeof i==="string"){i=i.replace(Ka,Ma);var o=(La.exec(i)||["",
+""])[1].toLowerCase(),k=F[o]||F._default,n=k[0],r=b.createElement("div");for(r.innerHTML=k[1]+i+k[2];n--;)r=r.lastChild;if(!c.support.tbody){n=ib.test(i);o=o==="table"&&!n?r.firstChild&&r.firstChild.childNodes:k[1]==="<table>"&&!n?r.childNodes:[];for(k=o.length-1;k>=0;--k)c.nodeName(o[k],"tbody")&&!o[k].childNodes.length&&o[k].parentNode.removeChild(o[k])}!c.support.leadingWhitespace&&V.test(i)&&r.insertBefore(b.createTextNode(V.exec(i)[0]),r.firstChild);i=r.childNodes}if(i.nodeType)e.push(i);else e=
+c.merge(e,i)}}if(d)for(j=0;e[j];j++)if(f&&c.nodeName(e[j],"script")&&(!e[j].type||e[j].type.toLowerCase()==="text/javascript"))f.push(e[j].parentNode?e[j].parentNode.removeChild(e[j]):e[j]);else{e[j].nodeType===1&&e.splice.apply(e,[j+1,0].concat(c.makeArray(e[j].getElementsByTagName("script"))));d.appendChild(e[j])}return e},cleanData:function(a){for(var b,d,f=c.cache,e=c.event.special,j=c.support.deleteExpando,i=0,o;(o=a[i])!=null;i++)if(d=o[c.expando]){b=f[d];if(b.events)for(var k in b.events)e[k]?
+c.event.remove(o,k):Ca(o,k,b.handle);if(j)delete o[c.expando];else o.removeAttribute&&o.removeAttribute(c.expando);delete f[d]}}});var kb=/z-?index|font-?weight|opacity|zoom|line-?height/i,Na=/alpha\([^)]*\)/,Oa=/opacity=([^)]*)/,ha=/float/i,ia=/-([a-z])/ig,lb=/([A-Z])/g,mb=/^-?\d+(?:px)?$/i,nb=/^-?\d/,ob={position:"absolute",visibility:"hidden",display:"block"},pb=["Left","Right"],qb=["Top","Bottom"],rb=s.defaultView&&s.defaultView.getComputedStyle,Pa=c.support.cssFloat?"cssFloat":"styleFloat",ja=
+function(a,b){return b.toUpperCase()};c.fn.css=function(a,b){return X(this,a,b,true,function(d,f,e){if(e===w)return c.curCSS(d,f);if(typeof e==="number"&&!kb.test(f))e+="px";c.style(d,f,e)})};c.extend({style:function(a,b,d){if(!a||a.nodeType===3||a.nodeType===8)return w;if((b==="width"||b==="height")&&parseFloat(d)<0)d=w;var f=a.style||a,e=d!==w;if(!c.support.opacity&&b==="opacity"){if(e){f.zoom=1;b=parseInt(d,10)+""==="NaN"?"":"alpha(opacity="+d*100+")";a=f.filter||c.curCSS(a,"filter")||"";f.filter=
+Na.test(a)?a.replace(Na,b):b}return f.filter&&f.filter.indexOf("opacity=")>=0?parseFloat(Oa.exec(f.filter)[1])/100+"":""}if(ha.test(b))b=Pa;b=b.replace(ia,ja);if(e)f[b]=d;return f[b]},css:function(a,b,d,f){if(b==="width"||b==="height"){var e,j=b==="width"?pb:qb;function i(){e=b==="width"?a.offsetWidth:a.offsetHeight;f!=="border"&&c.each(j,function(){f||(e-=parseFloat(c.curCSS(a,"padding"+this,true))||0);if(f==="margin")e+=parseFloat(c.curCSS(a,"margin"+this,true))||0;else e-=parseFloat(c.curCSS(a,
+"border"+this+"Width",true))||0})}a.offsetWidth!==0?i():c.swap(a,ob,i);return Math.max(0,Math.round(e))}return c.curCSS(a,b,d)},curCSS:function(a,b,d){var f,e=a.style;if(!c.support.opacity&&b==="opacity"&&a.currentStyle){f=Oa.test(a.currentStyle.filter||"")?parseFloat(RegExp.$1)/100+"":"";return f===""?"1":f}if(ha.test(b))b=Pa;if(!d&&e&&e[b])f=e[b];else if(rb){if(ha.test(b))b="float";b=b.replace(lb,"-$1").toLowerCase();e=a.ownerDocument.defaultView;if(!e)return null;if(a=e.getComputedStyle(a,null))f=
+a.getPropertyValue(b);if(b==="opacity"&&f==="")f="1"}else if(a.currentStyle){d=b.replace(ia,ja);f=a.currentStyle[b]||a.currentStyle[d];if(!mb.test(f)&&nb.test(f)){b=e.left;var j=a.runtimeStyle.left;a.runtimeStyle.left=a.currentStyle.left;e.left=d==="fontSize"?"1em":f||0;f=e.pixelLeft+"px";e.left=b;a.runtimeStyle.left=j}}return f},swap:function(a,b,d){var f={};for(var e in b){f[e]=a.style[e];a.style[e]=b[e]}d.call(a);for(e in b)a.style[e]=f[e]}});if(c.expr&&c.expr.filters){c.expr.filters.hidden=function(a){var b=
+a.offsetWidth,d=a.offsetHeight,f=a.nodeName.toLowerCase()==="tr";return b===0&&d===0&&!f?true:b>0&&d>0&&!f?false:c.curCSS(a,"display")==="none"};c.expr.filters.visible=function(a){return!c.expr.filters.hidden(a)}}var sb=J(),tb=/<script(.|\s)*?\/script>/gi,ub=/select|textarea/i,vb=/color|date|datetime|email|hidden|month|number|password|range|search|tel|text|time|url|week/i,N=/=\?(&|$)/,ka=/\?/,wb=/(\?|&)_=.*?(&|$)/,xb=/^(\w+:)?\/\/([^\/?#]+)/,yb=/%20/g,zb=c.fn.load;c.fn.extend({load:function(a,b,d){if(typeof a!==
+"string")return zb.call(this,a);else if(!this.length)return this;var f=a.indexOf(" ");if(f>=0){var e=a.slice(f,a.length);a=a.slice(0,f)}f="GET";if(b)if(c.isFunction(b)){d=b;b=null}else if(typeof b==="object"){b=c.param(b,c.ajaxSettings.traditional);f="POST"}var j=this;c.ajax({url:a,type:f,dataType:"html",data:b,complete:function(i,o){if(o==="success"||o==="notmodified")j.html(e?c("<div />").append(i.responseText.replace(tb,"")).find(e):i.responseText);d&&j.each(d,[i.responseText,o,i])}});return this},
+serialize:function(){return c.param(this.serializeArray())},serializeArray:function(){return this.map(function(){return this.elements?c.makeArray(this.elements):this}).filter(function(){return this.name&&!this.disabled&&(this.checked||ub.test(this.nodeName)||vb.test(this.type))}).map(function(a,b){a=c(this).val();return a==null?null:c.isArray(a)?c.map(a,function(d){return{name:b.name,value:d}}):{name:b.name,value:a}}).get()}});c.each("ajaxStart ajaxStop ajaxComplete ajaxError ajaxSuccess ajaxSend".split(" "),
+function(a,b){c.fn[b]=function(d){return this.bind(b,d)}});c.extend({get:function(a,b,d,f){if(c.isFunction(b)){f=f||d;d=b;b=null}return c.ajax({type:"GET",url:a,data:b,success:d,dataType:f})},getScript:function(a,b){return c.get(a,null,b,"script")},getJSON:function(a,b,d){return c.get(a,b,d,"json")},post:function(a,b,d,f){if(c.isFunction(b)){f=f||d;d=b;b={}}return c.ajax({type:"POST",url:a,data:b,success:d,dataType:f})},ajaxSetup:function(a){c.extend(c.ajaxSettings,a)},ajaxSettings:{url:location.href,
+global:true,type:"GET",contentType:"application/x-www-form-urlencoded",processData:true,async:true,xhr:A.XMLHttpRequest&&(A.location.protocol!=="file:"||!A.ActiveXObject)?function(){return new A.XMLHttpRequest}:function(){try{return new A.ActiveXObject("Microsoft.XMLHTTP")}catch(a){}},accepts:{xml:"application/xml, text/xml",html:"text/html",script:"text/javascript, application/javascript",json:"application/json, text/javascript",text:"text/plain",_default:"*/*"}},lastModified:{},etag:{},ajax:function(a){function b(){e.success&&
+e.success.call(k,o,i,x);e.global&&f("ajaxSuccess",[x,e])}function d(){e.complete&&e.complete.call(k,x,i);e.global&&f("ajaxComplete",[x,e]);e.global&&!--c.active&&c.event.trigger("ajaxStop")}function f(q,p){(e.context?c(e.context):c.event).trigger(q,p)}var e=c.extend(true,{},c.ajaxSettings,a),j,i,o,k=a&&a.context||e,n=e.type.toUpperCase();if(e.data&&e.processData&&typeof e.data!=="string")e.data=c.param(e.data,e.traditional);if(e.dataType==="jsonp"){if(n==="GET")N.test(e.url)||(e.url+=(ka.test(e.url)?
+"&":"?")+(e.jsonp||"callback")+"=?");else if(!e.data||!N.test(e.data))e.data=(e.data?e.data+"&":"")+(e.jsonp||"callback")+"=?";e.dataType="json"}if(e.dataType==="json"&&(e.data&&N.test(e.data)||N.test(e.url))){j=e.jsonpCallback||"jsonp"+sb++;if(e.data)e.data=(e.data+"").replace(N,"="+j+"$1");e.url=e.url.replace(N,"="+j+"$1");e.dataType="script";A[j]=A[j]||function(q){o=q;b();d();A[j]=w;try{delete A[j]}catch(p){}z&&z.removeChild(C)}}if(e.dataType==="script"&&e.cache===null)e.cache=false;if(e.cache===
+false&&n==="GET"){var r=J(),u=e.url.replace(wb,"$1_="+r+"$2");e.url=u+(u===e.url?(ka.test(e.url)?"&":"?")+"_="+r:"")}if(e.data&&n==="GET")e.url+=(ka.test(e.url)?"&":"?")+e.data;e.global&&!c.active++&&c.event.trigger("ajaxStart");r=(r=xb.exec(e.url))&&(r[1]&&r[1]!==location.protocol||r[2]!==location.host);if(e.dataType==="script"&&n==="GET"&&r){var z=s.getElementsByTagName("head")[0]||s.documentElement,C=s.createElement("script");C.src=e.url;if(e.scriptCharset)C.charset=e.scriptCharset;if(!j){var B=
+false;C.onload=C.onreadystatechange=function(){if(!B&&(!this.readyState||this.readyState==="loaded"||this.readyState==="complete")){B=true;b();d();C.onload=C.onreadystatechange=null;z&&C.parentNode&&z.removeChild(C)}}}z.insertBefore(C,z.firstChild);return w}var E=false,x=e.xhr();if(x){e.username?x.open(n,e.url,e.async,e.username,e.password):x.open(n,e.url,e.async);try{if(e.data||a&&a.contentType)x.setRequestHeader("Content-Type",e.contentType);if(e.ifModified){c.lastModified[e.url]&&x.setRequestHeader("If-Modified-Since",
+c.lastModified[e.url]);c.etag[e.url]&&x.setRequestHeader("If-None-Match",c.etag[e.url])}r||x.setRequestHeader("X-Requested-With","XMLHttpRequest");x.setRequestHeader("Accept",e.dataType&&e.accepts[e.dataType]?e.accepts[e.dataType]+", */*":e.accepts._default)}catch(ga){}if(e.beforeSend&&e.beforeSend.call(k,x,e)===false){e.global&&!--c.active&&c.event.trigger("ajaxStop");x.abort();return false}e.global&&f("ajaxSend",[x,e]);var g=x.onreadystatechange=function(q){if(!x||x.readyState===0||q==="abort"){E||
+d();E=true;if(x)x.onreadystatechange=c.noop}else if(!E&&x&&(x.readyState===4||q==="timeout")){E=true;x.onreadystatechange=c.noop;i=q==="timeout"?"timeout":!c.httpSuccess(x)?"error":e.ifModified&&c.httpNotModified(x,e.url)?"notmodified":"success";var p;if(i==="success")try{o=c.httpData(x,e.dataType,e)}catch(v){i="parsererror";p=v}if(i==="success"||i==="notmodified")j||b();else c.handleError(e,x,i,p);d();q==="timeout"&&x.abort();if(e.async)x=null}};try{var h=x.abort;x.abort=function(){x&&h.call(x);
+g("abort")}}catch(l){}e.async&&e.timeout>0&&setTimeout(function(){x&&!E&&g("timeout")},e.timeout);try{x.send(n==="POST"||n==="PUT"||n==="DELETE"?e.data:null)}catch(m){c.handleError(e,x,null,m);d()}e.async||g();return x}},handleError:function(a,b,d,f){if(a.error)a.error.call(a.context||a,b,d,f);if(a.global)(a.context?c(a.context):c.event).trigger("ajaxError",[b,a,f])},active:0,httpSuccess:function(a){try{return!a.status&&location.protocol==="file:"||a.status>=200&&a.status<300||a.status===304||a.status===
+1223||a.status===0}catch(b){}return false},httpNotModified:function(a,b){var d=a.getResponseHeader("Last-Modified"),f=a.getResponseHeader("Etag");if(d)c.lastModified[b]=d;if(f)c.etag[b]=f;return a.status===304||a.status===0},httpData:function(a,b,d){var f=a.getResponseHeader("content-type")||"",e=b==="xml"||!b&&f.indexOf("xml")>=0;a=e?a.responseXML:a.responseText;e&&a.documentElement.nodeName==="parsererror"&&c.error("parsererror");if(d&&d.dataFilter)a=d.dataFilter(a,b);if(typeof a==="string")if(b===
+"json"||!b&&f.indexOf("json")>=0)a=c.parseJSON(a);else if(b==="script"||!b&&f.indexOf("javascript")>=0)c.globalEval(a);return a},param:function(a,b){function d(i,o){if(c.isArray(o))c.each(o,function(k,n){b||/\[\]$/.test(i)?f(i,n):d(i+"["+(typeof n==="object"||c.isArray(n)?k:"")+"]",n)});else!b&&o!=null&&typeof o==="object"?c.each(o,function(k,n){d(i+"["+k+"]",n)}):f(i,o)}function f(i,o){o=c.isFunction(o)?o():o;e[e.length]=encodeURIComponent(i)+"="+encodeURIComponent(o)}var e=[];if(b===w)b=c.ajaxSettings.traditional;
+if(c.isArray(a)||a.jquery)c.each(a,function(){f(this.name,this.value)});else for(var j in a)d(j,a[j]);return e.join("&").replace(yb,"+")}});var la={},Ab=/toggle|show|hide/,Bb=/^([+-]=)?([\d+-.]+)(.*)$/,W,va=[["height","marginTop","marginBottom","paddingTop","paddingBottom"],["width","marginLeft","marginRight","paddingLeft","paddingRight"],["opacity"]];c.fn.extend({show:function(a,b){if(a||a===0)return this.animate(K("show",3),a,b);else{a=0;for(b=this.length;a<b;a++){var d=c.data(this[a],"olddisplay");
+this[a].style.display=d||"";if(c.css(this[a],"display")==="none"){d=this[a].nodeName;var f;if(la[d])f=la[d];else{var e=c("<"+d+" />").appendTo("body");f=e.css("display");if(f==="none")f="block";e.remove();la[d]=f}c.data(this[a],"olddisplay",f)}}a=0;for(b=this.length;a<b;a++)this[a].style.display=c.data(this[a],"olddisplay")||"";return this}},hide:function(a,b){if(a||a===0)return this.animate(K("hide",3),a,b);else{a=0;for(b=this.length;a<b;a++){var d=c.data(this[a],"olddisplay");!d&&d!=="none"&&c.data(this[a],
+"olddisplay",c.css(this[a],"display"))}a=0;for(b=this.length;a<b;a++)this[a].style.display="none";return this}},_toggle:c.fn.toggle,toggle:function(a,b){var d=typeof a==="boolean";if(c.isFunction(a)&&c.isFunction(b))this._toggle.apply(this,arguments);else a==null||d?this.each(function(){var f=d?a:c(this).is(":hidden");c(this)[f?"show":"hide"]()}):this.animate(K("toggle",3),a,b);return this},fadeTo:function(a,b,d){return this.filter(":hidden").css("opacity",0).show().end().animate({opacity:b},a,d)},
+animate:function(a,b,d,f){var e=c.speed(b,d,f);if(c.isEmptyObject(a))return this.each(e.complete);return this[e.queue===false?"each":"queue"](function(){var j=c.extend({},e),i,o=this.nodeType===1&&c(this).is(":hidden"),k=this;for(i in a){var n=i.replace(ia,ja);if(i!==n){a[n]=a[i];delete a[i];i=n}if(a[i]==="hide"&&o||a[i]==="show"&&!o)return j.complete.call(this);if((i==="height"||i==="width")&&this.style){j.display=c.css(this,"display");j.overflow=this.style.overflow}if(c.isArray(a[i])){(j.specialEasing=
+j.specialEasing||{})[i]=a[i][1];a[i]=a[i][0]}}if(j.overflow!=null)this.style.overflow="hidden";j.curAnim=c.extend({},a);c.each(a,function(r,u){var z=new c.fx(k,j,r);if(Ab.test(u))z[u==="toggle"?o?"show":"hide":u](a);else{var C=Bb.exec(u),B=z.cur(true)||0;if(C){u=parseFloat(C[2]);var E=C[3]||"px";if(E!=="px"){k.style[r]=(u||1)+E;B=(u||1)/z.cur(true)*B;k.style[r]=B+E}if(C[1])u=(C[1]==="-="?-1:1)*u+B;z.custom(B,u,E)}else z.custom(B,u,"")}});return true})},stop:function(a,b){var d=c.timers;a&&this.queue([]);
+this.each(function(){for(var f=d.length-1;f>=0;f--)if(d[f].elem===this){b&&d[f](true);d.splice(f,1)}});b||this.dequeue();return this}});c.each({slideDown:K("show",1),slideUp:K("hide",1),slideToggle:K("toggle",1),fadeIn:{opacity:"show"},fadeOut:{opacity:"hide"}},function(a,b){c.fn[a]=function(d,f){return this.animate(b,d,f)}});c.extend({speed:function(a,b,d){var f=a&&typeof a==="object"?a:{complete:d||!d&&b||c.isFunction(a)&&a,duration:a,easing:d&&b||b&&!c.isFunction(b)&&b};f.duration=c.fx.off?0:typeof f.duration===
+"number"?f.duration:c.fx.speeds[f.duration]||c.fx.speeds._default;f.old=f.complete;f.complete=function(){f.queue!==false&&c(this).dequeue();c.isFunction(f.old)&&f.old.call(this)};return f},easing:{linear:function(a,b,d,f){return d+f*a},swing:function(a,b,d,f){return(-Math.cos(a*Math.PI)/2+0.5)*f+d}},timers:[],fx:function(a,b,d){this.options=b;this.elem=a;this.prop=d;if(!b.orig)b.orig={}}});c.fx.prototype={update:function(){this.options.step&&this.options.step.call(this.elem,this.now,this);(c.fx.step[this.prop]||
+c.fx.step._default)(this);if((this.prop==="height"||this.prop==="width")&&this.elem.style)this.elem.style.display="block"},cur:function(a){if(this.elem[this.prop]!=null&&(!this.elem.style||this.elem.style[this.prop]==null))return this.elem[this.prop];return(a=parseFloat(c.css(this.elem,this.prop,a)))&&a>-10000?a:parseFloat(c.curCSS(this.elem,this.prop))||0},custom:function(a,b,d){function f(j){return e.step(j)}this.startTime=J();this.start=a;this.end=b;this.unit=d||this.unit||"px";this.now=this.start;
+this.pos=this.state=0;var e=this;f.elem=this.elem;if(f()&&c.timers.push(f)&&!W)W=setInterval(c.fx.tick,13)},show:function(){this.options.orig[this.prop]=c.style(this.elem,this.prop);this.options.show=true;this.custom(this.prop==="width"||this.prop==="height"?1:0,this.cur());c(this.elem).show()},hide:function(){this.options.orig[this.prop]=c.style(this.elem,this.prop);this.options.hide=true;this.custom(this.cur(),0)},step:function(a){var b=J(),d=true;if(a||b>=this.options.duration+this.startTime){this.now=
+this.end;this.pos=this.state=1;this.update();this.options.curAnim[this.prop]=true;for(var f in this.options.curAnim)if(this.options.curAnim[f]!==true)d=false;if(d){if(this.options.display!=null){this.elem.style.overflow=this.options.overflow;a=c.data(this.elem,"olddisplay");this.elem.style.display=a?a:this.options.display;if(c.css(this.elem,"display")==="none")this.elem.style.display="block"}this.options.hide&&c(this.elem).hide();if(this.options.hide||this.options.show)for(var e in this.options.curAnim)c.style(this.elem,
+e,this.options.orig[e]);this.options.complete.call(this.elem)}return false}else{e=b-this.startTime;this.state=e/this.options.duration;a=this.options.easing||(c.easing.swing?"swing":"linear");this.pos=c.easing[this.options.specialEasing&&this.options.specialEasing[this.prop]||a](this.state,e,0,1,this.options.duration);this.now=this.start+(this.end-this.start)*this.pos;this.update()}return true}};c.extend(c.fx,{tick:function(){for(var a=c.timers,b=0;b<a.length;b++)a[b]()||a.splice(b--,1);a.length||
+c.fx.stop()},stop:function(){clearInterval(W);W=null},speeds:{slow:600,fast:200,_default:400},step:{opacity:function(a){c.style(a.elem,"opacity",a.now)},_default:function(a){if(a.elem.style&&a.elem.style[a.prop]!=null)a.elem.style[a.prop]=(a.prop==="width"||a.prop==="height"?Math.max(0,a.now):a.now)+a.unit;else a.elem[a.prop]=a.now}}});if(c.expr&&c.expr.filters)c.expr.filters.animated=function(a){return c.grep(c.timers,function(b){return a===b.elem}).length};c.fn.offset="getBoundingClientRect"in s.documentElement?
+function(a){var b=this[0];if(a)return this.each(function(e){c.offset.setOffset(this,a,e)});if(!b||!b.ownerDocument)return null;if(b===b.ownerDocument.body)return c.offset.bodyOffset(b);var d=b.getBoundingClientRect(),f=b.ownerDocument;b=f.body;f=f.documentElement;return{top:d.top+(self.pageYOffset||c.support.boxModel&&f.scrollTop||b.scrollTop)-(f.clientTop||b.clientTop||0),left:d.left+(self.pageXOffset||c.support.boxModel&&f.scrollLeft||b.scrollLeft)-(f.clientLeft||b.clientLeft||0)}}:function(a){var b=
+this[0];if(a)return this.each(function(r){c.offset.setOffset(this,a,r)});if(!b||!b.ownerDocument)return null;if(b===b.ownerDocument.body)return c.offset.bodyOffset(b);c.offset.initialize();var d=b.offsetParent,f=b,e=b.ownerDocument,j,i=e.documentElement,o=e.body;f=(e=e.defaultView)?e.getComputedStyle(b,null):b.currentStyle;for(var k=b.offsetTop,n=b.offsetLeft;(b=b.parentNode)&&b!==o&&b!==i;){if(c.offset.supportsFixedPosition&&f.position==="fixed")break;j=e?e.getComputedStyle(b,null):b.currentStyle;
+k-=b.scrollTop;n-=b.scrollLeft;if(b===d){k+=b.offsetTop;n+=b.offsetLeft;if(c.offset.doesNotAddBorder&&!(c.offset.doesAddBorderForTableAndCells&&/^t(able|d|h)$/i.test(b.nodeName))){k+=parseFloat(j.borderTopWidth)||0;n+=parseFloat(j.borderLeftWidth)||0}f=d;d=b.offsetParent}if(c.offset.subtractsBorderForOverflowNotVisible&&j.overflow!=="visible"){k+=parseFloat(j.borderTopWidth)||0;n+=parseFloat(j.borderLeftWidth)||0}f=j}if(f.position==="relative"||f.position==="static"){k+=o.offsetTop;n+=o.offsetLeft}if(c.offset.supportsFixedPosition&&
+f.position==="fixed"){k+=Math.max(i.scrollTop,o.scrollTop);n+=Math.max(i.scrollLeft,o.scrollLeft)}return{top:k,left:n}};c.offset={initialize:function(){var a=s.body,b=s.createElement("div"),d,f,e,j=parseFloat(c.curCSS(a,"marginTop",true))||0;c.extend(b.style,{position:"absolute",top:0,left:0,margin:0,border:0,width:"1px",height:"1px",visibility:"hidden"});b.innerHTML="<div style='position:absolute;top:0;left:0;margin:0;border:5px solid #000;padding:0;width:1px;height:1px;'><div></div></div><table style='position:absolute;top:0;left:0;margin:0;border:5px solid #000;padding:0;width:1px;height:1px;' cellpadding='0' cellspacing='0'><tr><td></td></tr></table>";
+a.insertBefore(b,a.firstChild);d=b.firstChild;f=d.firstChild;e=d.nextSibling.firstChild.firstChild;this.doesNotAddBorder=f.offsetTop!==5;this.doesAddBorderForTableAndCells=e.offsetTop===5;f.style.position="fixed";f.style.top="20px";this.supportsFixedPosition=f.offsetTop===20||f.offsetTop===15;f.style.position=f.style.top="";d.style.overflow="hidden";d.style.position="relative";this.subtractsBorderForOverflowNotVisible=f.offsetTop===-5;this.doesNotIncludeMarginInBodyOffset=a.offsetTop!==j;a.removeChild(b);
+c.offset.initialize=c.noop},bodyOffset:function(a){var b=a.offsetTop,d=a.offsetLeft;c.offset.initialize();if(c.offset.doesNotIncludeMarginInBodyOffset){b+=parseFloat(c.curCSS(a,"marginTop",true))||0;d+=parseFloat(c.curCSS(a,"marginLeft",true))||0}return{top:b,left:d}},setOffset:function(a,b,d){if(/static/.test(c.curCSS(a,"position")))a.style.position="relative";var f=c(a),e=f.offset(),j=parseInt(c.curCSS(a,"top",true),10)||0,i=parseInt(c.curCSS(a,"left",true),10)||0;if(c.isFunction(b))b=b.call(a,
+d,e);d={top:b.top-e.top+j,left:b.left-e.left+i};"using"in b?b.using.call(a,d):f.css(d)}};c.fn.extend({position:function(){if(!this[0])return null;var a=this[0],b=this.offsetParent(),d=this.offset(),f=/^body|html$/i.test(b[0].nodeName)?{top:0,left:0}:b.offset();d.top-=parseFloat(c.curCSS(a,"marginTop",true))||0;d.left-=parseFloat(c.curCSS(a,"marginLeft",true))||0;f.top+=parseFloat(c.curCSS(b[0],"borderTopWidth",true))||0;f.left+=parseFloat(c.curCSS(b[0],"borderLeftWidth",true))||0;return{top:d.top-
+f.top,left:d.left-f.left}},offsetParent:function(){return this.map(function(){for(var a=this.offsetParent||s.body;a&&!/^body|html$/i.test(a.nodeName)&&c.css(a,"position")==="static";)a=a.offsetParent;return a})}});c.each(["Left","Top"],function(a,b){var d="scroll"+b;c.fn[d]=function(f){var e=this[0],j;if(!e)return null;if(f!==w)return this.each(function(){if(j=wa(this))j.scrollTo(!a?f:c(j).scrollLeft(),a?f:c(j).scrollTop());else this[d]=f});else return(j=wa(e))?"pageXOffset"in j?j[a?"pageYOffset":
+"pageXOffset"]:c.support.boxModel&&j.document.documentElement[d]||j.document.body[d]:e[d]}});c.each(["Height","Width"],function(a,b){var d=b.toLowerCase();c.fn["inner"+b]=function(){return this[0]?c.css(this[0],d,false,"padding"):null};c.fn["outer"+b]=function(f){return this[0]?c.css(this[0],d,false,f?"margin":"border"):null};c.fn[d]=function(f){var e=this[0];if(!e)return f==null?null:this;if(c.isFunction(f))return this.each(function(j){var i=c(this);i[d](f.call(this,j,i[d]()))});return"scrollTo"in
+e&&e.document?e.document.compatMode==="CSS1Compat"&&e.document.documentElement["client"+b]||e.document.body["client"+b]:e.nodeType===9?Math.max(e.documentElement["client"+b],e.body["scroll"+b],e.documentElement["scroll"+b],e.body["offset"+b],e.documentElement["offset"+b]):f===w?c.css(e,d):this.css(d,typeof f==="string"?f:f+"px")}});A.jQuery=A.$=c})(window);

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

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

Added: www-releases/trunk/3.6.1/docs/_static/llvm-theme.css
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/_static/llvm-theme.css?rev=238135&view=auto
==============================================================================
--- www-releases/trunk/3.6.1/docs/_static/llvm-theme.css (added)
+++ www-releases/trunk/3.6.1/docs/_static/llvm-theme.css Mon May 25 08:53:02 2015
@@ -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.6.1/docs/_static/llvm.css
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/_static/llvm.css?rev=238135&view=auto
==============================================================================
--- www-releases/trunk/3.6.1/docs/_static/llvm.css (added)
+++ www-releases/trunk/3.6.1/docs/_static/llvm.css Mon May 25 08:53:02 2015
@@ -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.6.1/docs/_static/logo.png
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/_static/logo.png?rev=238135&view=auto
==============================================================================
Binary file - no diff available.

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

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

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

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

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

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

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

Added: www-releases/trunk/3.6.1/docs/_static/pygments.css
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/_static/pygments.css?rev=238135&view=auto
==============================================================================
--- www-releases/trunk/3.6.1/docs/_static/pygments.css (added)
+++ www-releases/trunk/3.6.1/docs/_static/pygments.css Mon May 25 08:53:02 2015
@@ -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.6.1/docs/_static/searchtools.js
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/_static/searchtools.js?rev=238135&view=auto
==============================================================================
--- www-releases/trunk/3.6.1/docs/_static/searchtools.js (added)
+++ www-releases/trunk/3.6.1/docs/_static/searchtools.js Mon May 25 08:53:02 2015
@@ -0,0 +1,560 @@
+/*
+ * searchtools.js_t
+ * ~~~~~~~~~~~~~~~~
+ *
+ * Sphinx JavaScript utilties for the full-text search.
+ *
+ * :copyright: Copyright 2007-2011 by the Sphinx team, see AUTHORS.
+ * :license: BSD, see LICENSE for details.
+ *
+ */
+
+/**
+ * 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.
+ */
+
+jQuery.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;
+}
+
+
+/**
+ * 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;
+  }
+}
+
+
+/**
+ * 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, success: null,
+            dataType: "script", cache: true});
+  },
+
+  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() {
+      Search._pulse_status = (Search._pulse_status + 1) % 4;
+      var dotString = '';
+      for (var 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
+   */
+  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);
+  },
+
+  query : function(query) {
+    var stopwords = ["and","then","into","it","as","are","in","if","for","no","there","their","was","is","be","to","that","but","they","not","such","with","by","a","on","these","of","will","this","near","the","or","at"];
+
+    // 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 (var i = 0; i < tmp.length; i++) {
+      if (tmp[i] != "") {
+          objectterms.push(tmp[i].toLowerCase());
+      }
+
+      if ($u.indexOf(stopwords, tmp[i]) != -1 || tmp[i].match(/^\d+$/) ||
+          tmp[i] == "") {
+        // skip this "word"
+        continue;
+      }
+      // stem the word
+      var word = stemmer.stemWord(tmp[i]).toLowerCase();
+      // select the correct list
+      if (word[0] == '-') {
+        var toAppend = excluded;
+        word = word.substr(1);
+      }
+      else {
+        var toAppend = searchterms;
+        hlterms.push(tmp[i].toLowerCase());
+      }
+      // only add if not already in the list
+      if (!$.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 filenames = this._index.filenames;
+    var titles = this._index.titles;
+    var terms = this._index.terms;
+    var fileMap = {};
+    var files = null;
+    // different result priorities
+    var importantResults = [];
+    var objectResults = [];
+    var regularResults = [];
+    var unimportantResults = [];
+    $('#search-progress').empty();
+
+    // lookup as object
+    for (var i = 0; i < objectterms.length; i++) {
+      var others = [].concat(objectterms.slice(0,i),
+                             objectterms.slice(i+1, objectterms.length))
+      var results = this.performObjectSearch(objectterms[i], others);
+      // Assume first word is most likely to be the object,
+      // other words more likely to be in description.
+      // Therefore put matches for earlier words first.
+      // (Results are eventually used in reverse order).
+      objectResults = results[0].concat(objectResults);
+      importantResults = results[1].concat(importantResults);
+      unimportantResults = results[2].concat(unimportantResults);
+    }
+
+    // perform the search on the required terms
+    for (var i = 0; i < searchterms.length; i++) {
+      var word = searchterms[i];
+      // no match but word was a required one
+      if ((files = terms[word]) == null)
+        break;
+      if (files.length == undefined) {
+        files = [files];
+      }
+      // create the mapping
+      for (var j = 0; j < files.length; j++) {
+        var 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 (var 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 (var i = 0; i < excluded.length; i++) {
+        if (terms[excluded[i]] == file ||
+            $.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)
+        regularResults.push([filenames[file], titles[file], '', null]);
+    }
+
+    // delete unused variables in order to not waste
+    // memory until list is retrieved completely
+    delete filenames, titles, terms;
+
+    // now sort the regular results descending by title
+    regularResults.sort(function(a, b) {
+      var left = a[1].toLowerCase();
+      var right = b[1].toLowerCase();
+      return (left > right) ? -1 : ((left < right) ? 1 : 0);
+    });
+
+    // combine all results
+    var results = unimportantResults.concat(regularResults)
+      .concat(objectResults).concat(importantResults);
+
+    // 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) {
+          $.get(DOCUMENTATION_OPTIONS.URL_ROOT + '_sources/' +
+                item[0] + '.txt', function(data) {
+            if (data != '') {
+              listItem.append($.makeSearchSummary(data, searchterms, hlterms));
+              Search.output.append(listItem);
+            }
+            listItem.slideDown(5, function() {
+              displayNextItem();
+            });
+          }, "text");
+        } 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();
+  },
+
+  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 importantResults = [];
+    var objectResults = [];
+    var unimportantResults = [];
+
+    for (var prefix in objects) {
+      for (var name in objects[prefix]) {
+        var fullname = (prefix ? prefix + '.' : '') + name;
+        if (fullname.toLowerCase().indexOf(object) > -1) {
+          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 (var i = 0; i < otherterms.length; i++) {
+              if (haystack.indexOf(otherterms[i]) == -1) {
+                allfound = false;
+                break;
+              }
+            }
+            if (!allfound) {
+              continue;
+            }
+          }
+          var descr = objname + _(', in ') + title;
+          anchor = match[3];
+          if (anchor == '')
+            anchor = fullname;
+          else if (anchor == '-')
+            anchor = objnames[match[1]][1] + '-' + fullname;
+          result = [filenames[match[0]], fullname, '#'+anchor, descr];
+          switch (match[2]) {
+          case 1: objectResults.push(result); break;
+          case 0: importantResults.push(result); break;
+          case 2: unimportantResults.push(result); break;
+          }
+        }
+      }
+    }
+
+    // sort results descending
+    objectResults.sort(function(a, b) {
+      return (a[1] > b[1]) ? -1 : ((a[1] < b[1]) ? 1 : 0);
+    });
+
+    importantResults.sort(function(a, b) {
+      return (a[1] > b[1]) ? -1 : ((a[1] < b[1]) ? 1 : 0);
+    });
+
+    unimportantResults.sort(function(a, b) {
+      return (a[1] > b[1]) ? -1 : ((a[1] < b[1]) ? 1 : 0);
+    });
+
+    return [importantResults, objectResults, unimportantResults]
+  }
+}
+
+$(document).ready(function() {
+  Search.init();
+});
\ No newline at end of file

Added: www-releases/trunk/3.6.1/docs/_static/underscore.js
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/_static/underscore.js?rev=238135&view=auto
==============================================================================
--- www-releases/trunk/3.6.1/docs/_static/underscore.js (added)
+++ www-releases/trunk/3.6.1/docs/_static/underscore.js Mon May 25 08:53:02 2015
@@ -0,0 +1,23 @@
+// Underscore.js 0.5.5
+// (c) 2009 Jeremy Ashkenas, DocumentCloud Inc.
+// Underscore is freely distributable under the terms of the MIT license.
+// Portions of Underscore are inspired by or borrowed from Prototype.js,
+// Oliver Steele's Functional, and John Resig's Micro-Templating.
+// For all details and documentation:
+// http://documentcloud.github.com/underscore/
+(function(){var j=this,n=j._,i=function(a){this._wrapped=a},m=typeof StopIteration!=="undefined"?StopIteration:"__break__",b=j._=function(a){return new i(a)};if(typeof exports!=="undefined")exports._=b;var k=Array.prototype.slice,o=Array.prototype.unshift,p=Object.prototype.toString,q=Object.prototype.hasOwnProperty,r=Object.prototype.propertyIsEnumerable;b.VERSION="0.5.5";b.each=function(a,c,d){try{if(a.forEach)a.forEach(c,d);else if(b.isArray(a)||b.isArguments(a))for(var e=0,f=a.length;e<f;e++)c.call(d,
+a[e],e,a);else{var g=b.keys(a);f=g.length;for(e=0;e<f;e++)c.call(d,a[g[e]],g[e],a)}}catch(h){if(h!=m)throw h;}return a};b.map=function(a,c,d){if(a&&b.isFunction(a.map))return a.map(c,d);var e=[];b.each(a,function(f,g,h){e.push(c.call(d,f,g,h))});return e};b.reduce=function(a,c,d,e){if(a&&b.isFunction(a.reduce))return a.reduce(b.bind(d,e),c);b.each(a,function(f,g,h){c=d.call(e,c,f,g,h)});return c};b.reduceRight=function(a,c,d,e){if(a&&b.isFunction(a.reduceRight))return a.reduceRight(b.bind(d,e),c);
+var f=b.clone(b.toArray(a)).reverse();b.each(f,function(g,h){c=d.call(e,c,g,h,a)});return c};b.detect=function(a,c,d){var e;b.each(a,function(f,g,h){if(c.call(d,f,g,h)){e=f;b.breakLoop()}});return e};b.select=function(a,c,d){if(a&&b.isFunction(a.filter))return a.filter(c,d);var e=[];b.each(a,function(f,g,h){c.call(d,f,g,h)&&e.push(f)});return e};b.reject=function(a,c,d){var e=[];b.each(a,function(f,g,h){!c.call(d,f,g,h)&&e.push(f)});return e};b.all=function(a,c,d){c=c||b.identity;if(a&&b.isFunction(a.every))return a.every(c,
+d);var e=true;b.each(a,function(f,g,h){(e=e&&c.call(d,f,g,h))||b.breakLoop()});return e};b.any=function(a,c,d){c=c||b.identity;if(a&&b.isFunction(a.some))return a.some(c,d);var e=false;b.each(a,function(f,g,h){if(e=c.call(d,f,g,h))b.breakLoop()});return e};b.include=function(a,c){if(b.isArray(a))return b.indexOf(a,c)!=-1;var d=false;b.each(a,function(e){if(d=e===c)b.breakLoop()});return d};b.invoke=function(a,c){var d=b.rest(arguments,2);return b.map(a,function(e){return(c?e[c]:e).apply(e,d)})};b.pluck=
+function(a,c){return b.map(a,function(d){return d[c]})};b.max=function(a,c,d){if(!c&&b.isArray(a))return Math.max.apply(Math,a);var e={computed:-Infinity};b.each(a,function(f,g,h){g=c?c.call(d,f,g,h):f;g>=e.computed&&(e={value:f,computed:g})});return e.value};b.min=function(a,c,d){if(!c&&b.isArray(a))return Math.min.apply(Math,a);var e={computed:Infinity};b.each(a,function(f,g,h){g=c?c.call(d,f,g,h):f;g<e.computed&&(e={value:f,computed:g})});return e.value};b.sortBy=function(a,c,d){return b.pluck(b.map(a,
+function(e,f,g){return{value:e,criteria:c.call(d,e,f,g)}}).sort(function(e,f){e=e.criteria;f=f.criteria;return e<f?-1:e>f?1:0}),"value")};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){if(!a)return[];if(a.toArray)return a.toArray();if(b.isArray(a))return a;if(b.isArguments(a))return k.call(a);return b.values(a)};b.size=function(a){return b.toArray(a).length};b.first=function(a,c,d){return c&&!d?k.call(a,
+0,c):a[0]};b.rest=function(a,c,d){return k.call(a,b.isUndefined(c)||d?1:c)};b.last=function(a){return a[a.length-1]};b.compact=function(a){return b.select(a,function(c){return!!c})};b.flatten=function(a){return b.reduce(a,[],function(c,d){if(b.isArray(d))return c.concat(b.flatten(d));c.push(d);return c})};b.without=function(a){var c=b.rest(arguments);return b.select(a,function(d){return!b.include(c,d)})};b.uniq=function(a,c){return b.reduce(a,[],function(d,e,f){if(0==f||(c===true?b.last(d)!=e:!b.include(d,
+e)))d.push(e);return d})};b.intersect=function(a){var c=b.rest(arguments);return b.select(b.uniq(a),function(d){return b.all(c,function(e){return b.indexOf(e,d)>=0})})};b.zip=function(){for(var a=b.toArray(arguments),c=b.max(b.pluck(a,"length")),d=new Array(c),e=0;e<c;e++)d[e]=b.pluck(a,String(e));return d};b.indexOf=function(a,c){if(a.indexOf)return a.indexOf(c);for(var d=0,e=a.length;d<e;d++)if(a[d]===c)return d;return-1};b.lastIndexOf=function(a,c){if(a.lastIndexOf)return a.lastIndexOf(c);for(var d=
+a.length;d--;)if(a[d]===c)return d;return-1};b.range=function(a,c,d){var e=b.toArray(arguments),f=e.length<=1;a=f?0:e[0];c=f?e[0]:e[1];d=e[2]||1;e=Math.ceil((c-a)/d);if(e<=0)return[];e=new Array(e);f=a;for(var g=0;1;f+=d){if((d>0?f-c:c-f)>=0)return e;e[g++]=f}};b.bind=function(a,c){var d=b.rest(arguments,2);return function(){return a.apply(c||j,d.concat(b.toArray(arguments)))}};b.bindAll=function(a){var c=b.rest(arguments);if(c.length==0)c=b.functions(a);b.each(c,function(d){a[d]=b.bind(a[d],a)});
+return a};b.delay=function(a,c){var d=b.rest(arguments,2);return setTimeout(function(){return a.apply(a,d)},c)};b.defer=function(a){return b.delay.apply(b,[a,1].concat(b.rest(arguments)))};b.wrap=function(a,c){return function(){var d=[a].concat(b.toArray(arguments));return c.apply(c,d)}};b.compose=function(){var a=b.toArray(arguments);return function(){for(var c=b.toArray(arguments),d=a.length-1;d>=0;d--)c=[a[d].apply(this,c)];return c[0]}};b.keys=function(a){if(b.isArray(a))return b.range(0,a.length);
+var c=[];for(var d in a)q.call(a,d)&&c.push(d);return c};b.values=function(a){return b.map(a,b.identity)};b.functions=function(a){return b.select(b.keys(a),function(c){return b.isFunction(a[c])}).sort()};b.extend=function(a,c){for(var d in c)a[d]=c[d];return a};b.clone=function(a){if(b.isArray(a))return a.slice(0);return b.extend({},a)};b.tap=function(a,c){c(a);return a};b.isEqual=function(a,c){if(a===c)return true;var d=typeof a;if(d!=typeof c)return false;if(a==c)return true;if(!a&&c||a&&!c)return false;
+if(a.isEqual)return a.isEqual(c);if(b.isDate(a)&&b.isDate(c))return a.getTime()===c.getTime();if(b.isNaN(a)&&b.isNaN(c))return true;if(b.isRegExp(a)&&b.isRegExp(c))return a.source===c.source&&a.global===c.global&&a.ignoreCase===c.ignoreCase&&a.multiline===c.multiline;if(d!=="object")return false;if(a.length&&a.length!==c.length)return false;d=b.keys(a);var e=b.keys(c);if(d.length!=e.length)return false;for(var f in a)if(!b.isEqual(a[f],c[f]))return false;return true};b.isEmpty=function(a){return b.keys(a).length==
+0};b.isElement=function(a){return!!(a&&a.nodeType==1)};b.isArray=function(a){return!!(a&&a.concat&&a.unshift)};b.isArguments=function(a){return a&&b.isNumber(a.length)&&!b.isArray(a)&&!r.call(a,"length")};b.isFunction=function(a){return!!(a&&a.constructor&&a.call&&a.apply)};b.isString=function(a){return!!(a===""||a&&a.charCodeAt&&a.substr)};b.isNumber=function(a){return p.call(a)==="[object Number]"};b.isDate=function(a){return!!(a&&a.getTimezoneOffset&&a.setUTCFullYear)};b.isRegExp=function(a){return!!(a&&
+a.test&&a.exec&&(a.ignoreCase||a.ignoreCase===false))};b.isNaN=function(a){return b.isNumber(a)&&isNaN(a)};b.isNull=function(a){return a===null};b.isUndefined=function(a){return typeof a=="undefined"};b.noConflict=function(){j._=n;return this};b.identity=function(a){return a};b.breakLoop=function(){throw m;};var s=0;b.uniqueId=function(a){var c=s++;return a?a+c:c};b.template=function(a,c){a=new Function("obj","var p=[],print=function(){p.push.apply(p,arguments);};with(obj){p.push('"+a.replace(/[\r\t\n]/g,
+" ").replace(/'(?=[^%]*%>)/g,"\t").split("'").join("\\'").split("\t").join("'").replace(/<%=(.+?)%>/g,"',$1,'").split("<%").join("');").split("%>").join("p.push('")+"');}return p.join('');");return c?a(c):a};b.forEach=b.each;b.foldl=b.inject=b.reduce;b.foldr=b.reduceRight;b.filter=b.select;b.every=b.all;b.some=b.any;b.head=b.first;b.tail=b.rest;b.methods=b.functions;var l=function(a,c){return c?b(a).chain():a};b.each(b.functions(b),function(a){var c=b[a];i.prototype[a]=function(){var d=b.toArray(arguments);
+o.call(d,this._wrapped);return l(c.apply(b,d),this._chain)}});b.each(["pop","push","reverse","shift","sort","splice","unshift"],function(a){var c=Array.prototype[a];i.prototype[a]=function(){c.apply(this._wrapped,arguments);return l(this._wrapped,this._chain)}});b.each(["concat","join","slice"],function(a){var c=Array.prototype[a];i.prototype[a]=function(){return l(c.apply(this._wrapped,arguments),this._chain)}});i.prototype.chain=function(){this._chain=true;return this};i.prototype.value=function(){return this._wrapped}})();

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

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

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

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

Added: www-releases/trunk/3.6.1/docs/_static/websupport.js
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/_static/websupport.js?rev=238135&view=auto
==============================================================================
--- www-releases/trunk/3.6.1/docs/_static/websupport.js (added)
+++ www-releases/trunk/3.6.1/docs/_static/websupport.js Mon May 25 08:53:02 2015
@@ -0,0 +1,808 @@
+/*
+ * websupport.js
+ * ~~~~~~~~~~~~~
+ *
+ * sphinx.websupport utilties for all documentation.
+ *
+ * :copyright: Copyright 2007-2011 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.6.1/docs/genindex.html
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/genindex.html?rev=238135&view=auto
==============================================================================
--- www-releases/trunk/3.6.1/docs/genindex.html (added)
+++ www-releases/trunk/3.6.1/docs/genindex.html Mon May 25 08:53:02 2015
@@ -0,0 +1,2238 @@
+
+
+
+
+<!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.6 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.6',
+        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.6 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>
+    --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--help">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>
+    --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>
+    --param NAME, --param NAME=VALUE
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption--param">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>
+    --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-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>
+    -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-b">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -c, --branch-counts
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-c">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>
+    -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>
+    -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-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>
+    -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>
+    -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-f">command line option</a>
+  </dt>
+
+      </dl></dd>
+  </dl></td>
+  <td style="width: 33%" valign="top"><dl>
+      
+  <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>
+    -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>
+    -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>
+      
+  <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/llvm-link.html#cmdoption-help">[4]</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>
+    -j N, --threads=N
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/lit.html#cmdoption-j">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -l, --long-file-names
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-l">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>
+    -march=<arch>
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llc.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>
+  </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>
+    -mtriple=<target triple>
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llc.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-n">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>
+    -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-o">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=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/opt.html#cmdoption-p">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, --preserve-paths
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-p">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>
+    -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>
+    -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>
+    -size size
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-stress.html#cmdoption-size">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -stats
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-stats">command line option</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>
+    -time-passes
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-time-passes">command line option</a>
+  </dt>
+
+      </dl></dd>
+      
+  <dt>
+    -u, --unconditional-branches
+  </dt>
+
+      <dd><dl>
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-u">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-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/llvm-cov.html#cmdoption-version">[2]</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/tblgen.html#cmdoption-tblgen-version">tblgen 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/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/llvm-cov.html#cmdoption--help">--help</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/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--param">--param NAME, --param NAME=VALUE</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/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/llvm-cov.html#cmdoption-a">-a, --all-blocks</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-b">-b, --branch-probabilities</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-c">-c, --branch-counts</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/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/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-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/llvm-cov.html#cmdoption-f">-f, --function-summaries</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/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/llvm-link.html#cmdoption-help">[4]</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/llvm-cov.html#cmdoption-l">-l, --long-file-names</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/opt.html#cmdoption-load">-load=<plugin></a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption-march">-march=<arch></a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption-mattr">-mattr=a1,+a2,-a3,...</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption-mcpu">-mcpu=<cpuname></a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llc.html#cmdoption-mtriple">-mtriple=<target triple></a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-n">-n, --no-output</a>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-readobj.html#cmdoption-needed-libs">-needed-libs</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-cov.html#cmdoption-o">-o=<DIR|FILE>, --object-directory=<DIR>, --object-file=<FILE></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/llvm-cov.html#cmdoption-p">-p, --preserve-paths</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/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/opt.html#cmdoption-stats">-stats</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>
+  </dt>
+
+        
+  <dt><a href="CommandGuide/llvm-cov.html#cmdoption-u">-u, --unconditional-branches</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/llvm-cov.html#cmdoption-version">[2]</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-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--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>
+  </dl></td>
+  <td style="width: 33%" valign="top"><dl>
+      
+  <dt>
+    llvm-profdata-merge command line option
+  </dt>
+
+      <dd><dl>
+        
+  <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-output">-output=output, -o=output</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-output">-output=output, -o=output</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-2014, LLVM Project.
+      Last updated on 2015-05-25.
+      Created using <a href="http://sphinx.pocoo.org/">Sphinx</a> 1.1.3.
+    </div>
+  </body>
+</html>
\ No newline at end of file

Added: www-releases/trunk/3.6.1/docs/index.html
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/index.html?rev=238135&view=auto
==============================================================================
--- www-releases/trunk/3.6.1/docs/index.html (added)
+++ www-releases/trunk/3.6.1/docs/index.html Mon May 25 08:53:02 2015
@@ -0,0 +1,378 @@
+
+
+<!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.6 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.6',
+        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.6 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>
+</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>
+</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="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>Accurate 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="R600Usage.html"><em>User Guide for R600 Back-end</em></a></dt>
+<dd>This document describes how to use the R600 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>
+</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="MakefileGuide.html"><em>LLVM Makefile Guide</em></a></dt>
+<dd>Describes how the LLVM makefiles work and how to use them.</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.cs.uiuc.edu/mailman/listinfo/llvmdev">Developer’s List (llvmdev)</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.cs.uiuc.edu/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.cs.uiuc.edu/pipermail/llvmbugs/">Bugs & Patches Archive (llvmbugs)</a></dt>
+<dd>This list gets emailed every time a bug is opened and closed. It is
+higher volume than the LLVMdev list.</dd>
+<dt><a class="reference external" href="http://lists.cs.uiuc.edu/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.cs.uiuc.edu/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-2014, LLVM Project.
+      Last updated on 2015-05-25.
+      Created using <a href="http://sphinx.pocoo.org/">Sphinx</a> 1.1.3.
+    </div>
+  </body>
+</html>
\ No newline at end of file

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

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

Added: www-releases/trunk/3.6.1/docs/search.html
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/search.html?rev=238135&view=auto
==============================================================================
--- www-releases/trunk/3.6.1/docs/search.html (added)
+++ www-releases/trunk/3.6.1/docs/search.html Mon May 25 08:53:02 2015
@@ -0,0 +1,110 @@
+
+
+<!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.6 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.6',
+        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.6 documentation" href="index.html" />
+  <script type="text/javascript">
+    jQuery(function() { Search.loadIndex("searchindex.js"); });
+  </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-2014, LLVM Project.
+      Last updated on 2015-05-25.
+      Created using <a href="http://sphinx.pocoo.org/">Sphinx</a> 1.1.3.
+    </div>
+  </body>
+</html>
\ No newline at end of file

Added: www-releases/trunk/3.6.1/docs/searchindex.js
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/searchindex.js?rev=238135&view=auto
==============================================================================
--- www-releases/trunk/3.6.1/docs/searchindex.js (added)
+++ www-releases/trunk/3.6.1/docs/searchindex.js Mon May 25 08:53:02 2015
@@ -0,0 +1 @@
+Search.setIndex({objects:{"":{"--stats":[77,0,1,"cmdoption--stats"],"-B":[110,0,1,"cmdoption-llvm-nm-B"],"-O":[77,0,1,"cmdoption-O"],"-seed":[42,0,1,"cmdoption-seed"],"-I":[114,0,1,"cmdoption-tblgen-I"],"-gen-register-info":[114,0,1,"cmdoption-tblgen-gen-register-info"],"--x86-asm-syntax":[77,0,1,"cmdoption--x86-asm-syntax"],"-S":[75,0,1,"cmdoption-S"],"-mattr":[77,0,1,"cmdoption-mattr"],"-counts":[109,0,1,"cmdoption-llvm-profdata-show-counts"],"-gen-subtarget":[114,0,1,"cmdoption-tblgen-gen-subtarget"],"-d":[106,0,1,"cmdoption-d"],"-f":[75,0,1,"cmdoption-f"],"-a":[94,0,1,"cmdoption-a"],"-c":[94,0,1,"cmdoption-c"],"-demangle":[79,0,1,"cmdoption-demangle"],"--no-progress-bar":[1,0,1,"cmdoption--no-progress-bar"],"-l":[94,0,1,"cmdoption-l"],"-o":[114,0,1,"cmdoption-tblgen-o"],"-n":[94,0,1,"cmdoption-n"],"-h":[1,0,1,"cmdoption-h"],"--defined-only":[110,0,1,"cmdoption-llvm-nm--defined-only"],"-j":[1,0,1,"cmdoption-j"],"-u":[94,0,1,"cmdoption-u"],"-v":[106,0,1,"cmdoption-v"],"-q":[1,0,1,
 "cmdoption-q"],"-p":[75,0,1,"cmdoption-p"],"-s":[1,0,1,"cmdoption-s"],"-gen-dag-isel":[114,0,1,"cmdoption-tblgen-gen-dag-isel"],"-use-symbol-table":[79,0,1,"cmdoption-use-symbol-table"],"--max-tests":[1,0,1,"cmdoption--max-tests"],"-class":[114,0,1,"cmdoption-tblgen-class"],"-section-relocations":[57,0,1,"cmdoption-section-relocations"],"-all-functions":[109,0,1,"cmdoption-llvm-profdata-show-all-functions"],"--show-xfail":[1,0,1,"cmdoption--show-xfail"],"-nodetails":[36,0,1,"cmdoption-llvm-bcanalyzer-nodetails"],"-gen-instr-info":[114,0,1,"cmdoption-tblgen-gen-instr-info"],"-P":[110,0,1,"cmdoption-llvm-nm-P"],"--print-file-name":[110,0,1,"cmdoption-llvm-nm--print-file-name"],"-stats":[75,0,1,"cmdoption-stats"],"-gen-asm-writer":[114,0,1,"cmdoption-tblgen-gen-asm-writer"],"-symbols":[57,0,1,"cmdoption-symbols"],"-print-sets":[114,0,1,"cmdoption-tblgen-print-sets"],"-program-headers":[57,0,1,"cmdoption-program-headers"],"--disable-fp-elim":[77,0,1,"cmdoption--disable-fp-elim"],"-obj":
 [79,0,1,"cmdoption-obj"],"--check-prefix":[5,0,1,"cmdoption--check-prefix"],"--show-suites":[1,0,1,"cmdoption--show-suites"],"-relocations":[57,0,1,"cmdoption-relocations"],"-needed-libs":[57,0,1,"cmdoption-needed-libs"],"--vg-leak":[1,0,1,"cmdoption--vg-leak"],"--enable-no-nans-fp-math":[77,0,1,"cmdoption--enable-no-nans-fp-math"],"-asmwriternum":[114,0,1,"cmdoption-tblgen-asmwriternum"],"-debug-dump":[89,0,1,"cmdoption-debug-dump"],"--print-machineinstrs":[77,0,1,"cmdoption--print-machineinstrs"],"-asmparsernum":[114,0,1,"cmdoption-tblgen-asmparsernum"],"-section-symbols":[57,0,1,"cmdoption-section-symbols"],"--print-size":[110,0,1,"cmdoption-llvm-nm--print-size"],"--config-prefix":[1,0,1,"cmdoption--config-prefix"],"-sections":[57,0,1,"cmdoption-sections"],"-function":[109,0,1,"cmdoption-llvm-profdata-show-function"],"-print-records":[114,0,1,"cmdoption-tblgen-print-records"],"-gen-dfa-packetizer":[114,0,1,"cmdoption-tblgen-gen-dfa-packetizer"],"--load":[77,0,1,"cmdoption--load"]
 ,"-dump":[36,0,1,"cmdoption-llvm-bcanalyzer-dump"],"--dynamic":[110,0,1,"cmdoption-llvm-nm--dynamic"],"-b":[94,0,1,"cmdoption-b"],"--spiller":[77,0,1,"cmdoption--spiller"],"-gen-intrinsic":[114,0,1,"cmdoption-tblgen-gen-intrinsic"],"--enable-unsafe-fp-math":[77,0,1,"cmdoption--enable-unsafe-fp-math"],"-verify-each":[75,0,1,"cmdoption-verify-each"],"-strip-debug":[75,0,1,"cmdoption-strip-debug"],"--size-sort":[110,0,1,"cmdoption-llvm-nm--size-sort"],"-version":[114,0,1,"cmdoption-tblgen-version"],"-size":[42,0,1,"cmdoption-size"],"--enable-no-infs-fp-math":[77,0,1,"cmdoption--enable-no-infs-fp-math"],"--path":[1,0,1,"cmdoption--path"],"-time-passes":[75,0,1,"cmdoption-time-passes"],"-march":[77,0,1,"cmdoption-march"],"--show-unsupported":[1,0,1,"cmdoption--show-unsupported"],"-disable-inlining":[75,0,1,"cmdoption-disable-inlining"],"--time-passes":[77,0,1,"cmdoption--time-passes"],"--vg":[1,0,1,"cmdoption--vg"],"--show-tests":[1,0,1,"cmdoption--show-tests"],"-help":[109,0,1,"cmdoptio
 n-llvm-profdata-merge-help"],"--shuffle":[1,0,1,"cmdoption--shuffle"],"--extern-only":[110,0,1,"cmdoption-llvm-nm--extern-only"],"-load":[75,0,1,"cmdoption-load"],"-expand-relocs":[57,0,1,"cmdoption-expand-relocs"],"--disable-excess-fp-precision":[77,0,1,"cmdoption--disable-excess-fp-precision"],"--format":[110,0,1,"cmdoption-llvm-nm--format"],"-print-enums":[114,0,1,"cmdoption-tblgen-print-enums"],"-filetype":[77,0,1,"cmdoption-filetype"],"-gen-emitter":[114,0,1,"cmdoption-tblgen-gen-emitter"],"-unwind":[57,0,1,"cmdoption-unwind"],"-gen-pseudo-lowering":[114,0,1,"cmdoption-tblgen-gen-pseudo-lowering"],"-verify":[36,0,1,"cmdoption-llvm-bcanalyzer-verify"],"-gen-tgt-intrinsic":[114,0,1,"cmdoption-tblgen-gen-tgt-intrinsic"],"--help":[94,0,1,"cmdoption--help"],"--implicit-check-not":[5,0,1,"cmdoption--implicit-check-not"],"-section-data":[57,0,1,"cmdoption-section-data"],"-disable-opt":[75,0,1,"cmdoption-disable-opt"],"-mcpu":[77,0,1,"cmdoption-mcpu"],"-file-headers":[57,0,1,"cmdoption
 -file-headers"],"--undefined-only":[110,0,1,"cmdoption-llvm-nm--undefined-only"],"-debug":[75,0,1,"cmdoption-debug"],"--param":[1,0,1,"cmdoption--param"],"-dynamic-table":[57,0,1,"cmdoption-dynamic-table"],"-inlining":[79,0,1,"cmdoption-inlining"],"--vg-arg":[1,0,1,"cmdoption--vg-arg"],"-functions":[79,0,1,"cmdoption-functions"],"--max-time":[1,0,1,"cmdoption--max-time"],"--debug":[1,0,1,"cmdoption--debug"],"-dyn-symbols":[57,0,1,"cmdoption-dyn-symbols"],"-mtriple":[77,0,1,"cmdoption-mtriple"],"--numeric-sort":[110,0,1,"cmdoption-llvm-nm--numeric-sort"],"--strict-whitespace":[5,0,1,"cmdoption--strict-whitespace"],"-gen-fast-isel":[114,0,1,"cmdoption-tblgen-gen-fast-isel"],"-gen-disassembler":[114,0,1,"cmdoption-tblgen-gen-disassembler"],"-gen-asm-matcher":[114,0,1,"cmdoption-tblgen-gen-asm-matcher"],"--time-tests":[1,0,1,"cmdoption--time-tests"],"--no-sort":[110,0,1,"cmdoption-llvm-nm--no-sort"],"-dsym-hint":[79,0,1,"cmdoption-dsym-hint"],"--input-file":[5,0,1,"cmdoption--input-file
 "],"--debug-syms":[110,0,1,"cmdoption-llvm-nm--debug-syms"],"-gen-enhanced-disassembly-info":[114,0,1,"cmdoption-tblgen-gen-enhanced-disassembly-info"],"--regalloc":[77,0,1,"cmdoption--regalloc"],"-output":[109,0,1,"cmdoption-llvm-profdata-show-output"],"-default-arch":[79,0,1,"cmdoption-default-arch"]}},terms:{orthogon:86,interchang:[65,84,68],four:[84,111,52,40,41,20,1,103,74,68,78,8,102,70,19],prefix:[68,73,1,94,70,6,5,2,10,14,15,16,50,100,20,103,76,23,60,107,29,84,87,63,111,65,24,115],grokabl:68,is_open:8,francesco:30,repetit:84,add32ri8:6,globalvari:[76,16,38,11,102],identityprop:16,foldingsetnodeid:16,build_fcmp:[12,13,14,15,19],dbx:103,digit:[70,20,110,16],intregsregclass:52,emitconst:52,module_code_funct:111,basic_:115,n2118:68,delv:[12,48],f110:8,aliasa:70,dw_lang_c89:103,configstatusscript:65,distcheckdir:65,fpmad:103,mli:12,bitstream:111,seper:70,second:[30,84,0,32,33,1,93,68,69,4,70,66,38,39,96,41,5,97,45,47,11,73,13,16,19,52,102,74,20,103,55,76,23,107,24,91,85,88,111,10
 5],x86ii:52,r15d:6,r15b:6,alignstack:[70,111],thefpm:[39,45,2,47,48],constrast:40,r15w:6,errorf:[39,41,54,45,2,47,48],xchg:[70,86],cull:68,ongo:[73,29,25],noreturn:[70,49,111],visitxor:83,here:[91,32,33,34,93,35,68,69,4,98,70,6,71,37,38,39,84,8,41,5,43,97,45,2,47,48,10,11,49,73,12,13,14,15,16,18,19,66,52,101,74,90,20,99,103,76,102,96,23,60,83,29,40,85,86,87,108,88,54,113,65,28,24,115],gnu_hash:103,lowerswitch:30,accur:[37,38,39,30,74,90,40,103,94,11,70],image_file_machine_r4000:108,iseldagtodag:21,"0x20":103,golden:68,unic:20,bou_tru:20,unif:40,brought:32,substr:66,unix:[23,60,96,70,20,97,10,65,4,5,16],machinecodeemitt:52,content_disposition_typ:25,uint64_max:58,unit:[30,68,0,70,66,39,112,97,16,52,102,20,103,76,21,78,59,60,107,29,84,65,24,115],ldri:52,fstream:8,subpath:[26,1],destarglist:70,callgraph:[76,30],strike:[41,19],feat_jit_arm:84,until:[30,68,31,1,70,71,39,41,112,43,45,2,47,48,10,72,12,13,14,15,16,17,18,19,52,54,20,76,21,78,56,110,23,83,29,84,25,111,107],new_else_bb:[13,14,
 15],emitlabelplusoffset:74,jmp:70,relat:[30,91,31,32,1,93,68,69,70,8,41,2,47,48,10,73,12,14,84,16,19,52,102,103,76,21,40,25,26],notic:[97,60,101,8,41,32,84,45,25,49,102,15,16,19],hurt:68,exce:[68,70,103],hole:[20,70],herebi:68,unpack:[23,65,9,37],image_scn_align_128byt:108,generalis:[14,2],dagtodag:64,conceptu:[68,102,5,20,84,107,78,70,16],forexpr:[39,45,2,47,13,14,15],oftc:37,rework:[20,25,29],get_matcher_implement:21,al_superregsset:52,phabric:[37,25,82],dtor:[97,70],createfunct:39,replaceusesofwith:[59,16],doubletyp:16,caution:[65,86,73],fibonacci:[65,35,17,43],want:[30,61,91,32,33,34,94,35,68,69,4,70,6,37,38,39,84,8,41,5,43,97,9,46,47,48,10,11,49,45,12,13,15,16,17,18,19,52,102,101,20,99,64,103,76,23,60,82,24,40,87,62,25,50,111,54,113,65,105,29,115],umin:70,hasfp:52,codegen:[5,70,37,64,39,8,41,112,45,2,47,48,10,12,13,14,15,19,52,74,76,21,23,84,86,90],mcasmstream:84,shuffl:[1,70],hoc:[30,84,16],classifi:40,i686:[10,84,5],how:[30,61,91,31,32,33,1,34,67,93,35,68,54,69,98,70,6,66,37,
 38,39,84,8,41,5,43,97,9,2,47,48,10,11,49,45,12,13,14,15,16,17,18,19,51,52,53,101,20,99,64,103,76,113,21,78,56,102,58,96,23,60,82,73,83,24,40,86,87,63,25,88,50,111,107,26,65,105,28,115],hot:[29,70,49,58],fuzzer:24,actionscript:[38,11],macosx10:70,perspect:[101,40,73,76,107,70],lhse:[39,45],tls1_process_heartbeat:24,wrong:[39,40,29,61,68,65,4,97],beauti:[41,43,2,14,17,19],adc32rm:6,outoperandlist:[6,52],weakanylinkag:16,index2virtreg:84,passopt:76,isvalid:39,apint:16,alias:[30,38,52,40,32,29,84,11,49,111,88,102,70,20],"18th":102,prototypeast:[39,41,54,45,2,47,48],tok_for:[39,45,2,47],"0x3f":22,feedback:[76,113,24,25,93],assing:32,affect:[28,97,60,8,31,70,20,61,9,86,47,93,76,78,13,32,4,16,29,115],vari:[38,97,16,84,103,86,11,111,4,83],exported_symbol_list:65,sanitize_memori:70,fit:[30,68,102,70,20,84,103,47,25,78,13,16],fix:[91,31,32,33,1,93,68,70,6,38,84,41,5,43,97,45,11,15,16,17,18,19,52,102,20,103,76,58,23,59,29,61,85,86,25,88,111,54,105,28,115],"200000e":[13,47],xxxinstrdescriptor:5
 2,hidden:[68,16,20,84,46,67,103,76,94,111,56,70],easier:[30,61,31,86,68,70,6,64,39,8,41,54,97,45,98,10,15,16,18,19,100,74,21,82,84,40,25,26],aliasesset:40,proce:[31,32,59,74,107],imagstart:[14,2],"0x34":103,interrupt:[4,24,1,70,68],itanium:[104,22,107],sellect:21,kernelparam:8,initializecustomlow:74,loopinfo:76,dcmake_install_prefix:9,exprast:[39,41,54,45,2,47,48,18],accommod:[84,22,111,8],spotless:65,debug:[30,84,32,1,67,93,94,35,68,70,6,97,66,37,7,39,40,112,43,44,45,98,10,11,15,16,17,50,51,100,52,74,20,75,38,103,76,77,22,89,79,110,23,60,83,24,61,87,62,25,88,107,65,90],build_fadd:19,openfileforwrit:4,resum:[88,107,70,98],isloadfromstackslot:52,pinsrd_1:5,numentri:111,whip:[14,2],intregssuperclass:52,dst:[69,84,6,52,115],smp:76,only_tool:[23,65],llvm_lit_arg:60,adapt:[4,97,16,30],aliasdebugg:40,inteqclass:16,dse:[30,59,86,40],impract:16,committ:25,preservesourc:29,navig:[26,20,82],selectionkind:70,omiss:70,targetloweringobjectfil:84,gollvm:29,adc64ri32:6,f3_1:52,uiuc:25,f3_3:52,proj
 _src_root:[65,50],reformul:40,realstart:[14,2],pointstoconstantmemori:[70,40],att:[80,77,70],unabl:[59,70,18,115],disablelazycompil:16,"0x2e":103,confus:[68,96,52,102,16,25,32,70],s3_pkt:24,configurescriptflag:65,clariti:[13,103,47],wast:[71,105,45,103,88,15,16],psubusw:10,mingw:[35,84,60,93],mklib:65,wasn:[39,40,32,45,2,68,14,15],vhdl:29,isalnum:[39,41,54,43,45,2,47,48],evolut:30,llvmmemorymanagerallocatedatasectioncallback:88,signext:[29,70,111],setargstr:20,nobuiltin:70,master:[10,23,113,50,37],image_scn_mem_discard:108,similarli:[37,39,52,40,16,20,61,68,83,25,78,65,93,70,33],getnod:[64,52],image_sym_class_stat:108,linpack:0,addrrr:52,arrayidx1:70,arrayidx3:70,arrayidx2:70,arrayidx4:70,"0x3500000001652748":98,ntid:8,crawl:74,printdatadirect:52,lvalu:16,tree:[30,68,32,33,1,93,35,70,37,39,8,41,54,43,97,9,2,47,48,10,45,12,13,14,15,16,17,18,19,101,53,103,76,102,23,59,60,29,87,25,50,26,65],project:[68,32,33,1,67,93,35,37,64,104,43,97,10,73,17,50,53,103,23,60,24,63,25,88,26,65,29],wcha
 r_t:70,image_rel_i386_secrel:22,sdnode:[83,84,16,6,52],recheck:[30,65,32],uniniti:[74,115,70,102],aapc:[34,78],aforement:23,increment:[30,39,74,70,84,45,47,83,25,85,13,68,15,16],infring:25,incompat:[62,70],dozen:[34,49],sig_atomic_t:70,implicitus:84,musttail:70,browsabl:60,get_instrinfo_operand_types_enum:52,simplifi:[30,91,61,73,33,68,70,39,43,45,2,47,48,12,13,14,15,16,17,23,29,84,108,25],shall:[70,20,60,11,38],cpu2:91,object:[61,91,32,33,1,77,67,94,35,68,101,4,98,70,71,38,45,84,8,41,112,97,9,46,47,48,11,73,12,13,54,15,16,17,18,19,51,100,111,52,102,74,90,20,75,103,76,21,78,56,79,80,57,110,23,59,83,29,40,108,87,63,25,88,50,89,107,65,115,28,66],numloc:88,specifi:[72,30,61,107,0,73,33,1,93,94,35,68,4,109,70,6,66,37,7,39,95,84,8,41,5,97,45,2,47,48,10,11,49,42,92,12,13,14,15,16,18,19,100,52,102,74,54,20,75,38,103,76,21,22,89,79,80,57,110,96,23,60,106,83,29,40,86,87,91,77,88,50,111,112,26,65,114,28,115],letter:[39,52,20,45,2,68,111,65,14,15,70],breakpoint:[76,39,83,98],alwaysinlin:[70,11
 1],errorv:[39,41,45,2,47,48],getelementtyp:16,expr0rh:66,dagarg:28,purgev:111,dummi:[30,97,52,24,84,10,115],lpm:76,mayreadfrommemori:86,detriment:68,came:[13,38,110,11,47],explan:[32,97,60,101],addr2:79,functionattr:30,matchinstructionimpl:84,layout:[30,84,60,52,23,74,16,8,103,37,78,102,70,50],n_hash:103,ccmake:60,apach:[4,25],somefil:97,theme:[6,99],busi:25,rich:[37,27],exctyp:107,recursivetarget:65,plate:20,selectiondagbuild:84,enable_profil:[23,97,87,65],ceil:[70,0],replaceusesofwithonconst:59,addrr:52,smallvectorimpl:16,ppc_fp128:[32,70,111],hasopsizeprefix:6,patch:[23,39,82,37,74,73,29,68,48,10,113,35,25,88,49,59,12,93,70],emitstorecondit:86,sligtli:78,respond:[30,82,40],sjljehprepar:107,mandatori:[70,35,16,52],result:[30,61,107,0,31,32,33,1,93,94,35,68,69,4,98,70,6,71,37,64,39,95,84,8,41,5,97,45,2,47,48,10,73,12,13,14,15,16,18,19,66,52,102,74,54,20,75,103,76,78,56,80,96,23,109,83,29,40,86,87,91,63,25,88,111,112,65,24,115],respons:[30,25,40,74,16,20,53,85,55,91,76,21,88,93,65,8
 4,70,29],fail:[68,0,31,33,1,34,5,35,4,70,112,97,10,20,103,80,23,60,107,61,86,87,25,65],best:[23,38,61,30,107,43,40,68,103,87,88,25,11,78,54,80,84,16,97,18],dw_tag_reference_typ:103,heterogen:29,wikipedia:[26,13,70,47],copyleft:25,figur:[76,84,52,16,20,61,83,10,68,78,65,70],irc:[37,25,49,82],sysroot:[9,6],glasgow:70,xvf:35,never:[30,91,32,33,94,68,70,66,38,96,40,101,97,48,11,12,16,52,102,74,76,78,29,84,86,63,90],extend:[68,73,1,70,6,37,38,39,101,54,43,45,2,47,48,11,49,99,12,13,14,15,16,17,18,51,52,74,20,64,22,23,84,86,115],extens:[30,68,0,32,94,35,4,70,37,64,104,54,97,45,2,47,49,73,13,14,15,16,18,52,74,20,103,76,21,22,77,60,107,29,84,108,25,88,26,65],extent:[74,25,70,102,53],toler:[74,70,93],advertis:107,rtti:[37,68,60,101,107,62,16],"0f3f800000":8,accident:[76,4,20,68],atomicexpandpass:86,logic:[30,68,32,1,70,41,5,45,2,47,13,14,15,16,19,101,102,84,25,54,26,65],hh567368:68,compromis:16,assur:91,mattr:[80,77,5,52],creategvnpass:[39,45,2,47,48],"2nd":[70,16,115],dibuild:[39,103],makeli
 ght:68,diff:[23,68,82,30,44,67,10,25],summat:70,assum:[30,91,31,32,33,68,35,3,70,38,8,41,54,97,2,11,73,14,84,16,19,52,102,64,103,76,77,80,58,23,83,24,40,85,87,25,88,111,107,65],summar:[74,30,1,84],duplic:[30,90,25,96,40,73,70,20,84,68,103,21,22,24,32,4,54,16,6,18,49],frc:84,frb:84,fra:84,bewilder:65,union:[68,40,84,45,103,15,70],much:[30,61,91,31,45,68,36,101,4,70,6,38,84,8,41,54,97,9,46,48,10,11,73,12,15,16,18,19,52,90,20,64,103,76,96,23,82,83,24,40,86,62,63,25,88,50,113,105,28],frt:84,feat_disassembl:84,spir:29,life:[25,68,49],regul:76,mrm6m:52,type_code_x86_fp80:111,worker:24,ani:[0,1,4,5,6,8,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26,27,28,29,30,32,33,34,35,36,37,38,39,40,41,54,43,44,45,2,47,48,49,50,66,52,103,56,58,59,60,91,65,69,70,71,73,74,75,76,77,78,83,84,86,87,88,90,68,92,93,94,96,97,99,100,102,64,107,109,110,111,112,105,115],cufunct:8,lift:49,"0x16151f0":98,objectfil:71,hasfparmv8:6,image_scn_mem_not_cach:108,dissect:[66,8],paramattr_block:111,commerci:25,employ:2
 5,one_onli:22,debug_metadata_vers:39,emit_22:52,unop:[39,14,15,45,2],bio:24,rediscov:[38,11],filename0:66,lto_module_is_object_file_in_memori:90,globaldc:[30,16],createret:[39,41,45,2,47,48],format:[30,84,73,33,1,68,36,69,70,6,71,37,64,39,104,96,8,44,77,98,97,66,52,53,20,75,103,21,22,78,80,57,110,23,107,24,91,25,88,111,26,105,29,115],bikesh:101,generalcategori:20,falsedest:70,split:[30,64,52,102,32,20,84,85,103,83,25,78,86,70,50],immtypebit:6,functionpassmanag:[39,45,2,47,48],mmsa:29,annoat:27,reassoci:[30,39,45,2,47,48,59,12,13,14,15,70],cxx0x:68,dest1:70,fairli:[38,97,52,40,54,29,43,2,47,86,11,26,13,14,16,17,18],dest2:70,refil:32,ownership:[39,45,2,47,48,25,16],printdeclar:52,engin:[71,23,38,59,37,30,41,32,43,97,100,47,48,11,65,12,13,102,17],fprofil:[66,94],tune:[60,0,20,84,45,103,77,49,15,16],readcyclecount:70,bewar:[74,68],fucomip:84,nuzman:0,gzip:[23,93],unchang:[70,16,40],ordin:20,volunt:[31,113],phinod:[68,39,45,2,47],previous:[60,52,33,41,70,20,47,93,94,28,29,19],fintegr:29,
 typeless:29,easi:[84,31,32,33,1,68,70,38,45,41,54,43,9,47,48,10,11,12,13,15,16,17,18,19,101,74,103,76,21,23,60,24,91,87,63,25,111,26,105],bitwidth:[32,70,111],had:[8,32,91,86,76,88,78,36,4,105,70],ideal:[26,73,68,16,52],har:[23,50],hat:91,sanit:[24,60,29],ocamlbuild:[12,13,14,15,18,19],issimpl:86,preserv:[38,84,96,102,53,20,40,76,94,11,78,88,70],instrumen:66,st_mode:96,attrparsedattrkind:21,shadow:[39,52,74,45,2,47,88,13,14,15],isdeclar:[29,16],measur:96,specif:[30,84,0,31,33,1,93,35,68,4,70,6,71,37,38,104,96,8,5,43,97,2,10,11,49,99,14,16,17,18,66,52,102,74,64,103,76,77,22,80,57,23,60,107,24,91,86,87,25,88,111,54,26,65,27,28,29,115],fcmpinst:16,nonlazybind:70,remind:93,underli:[39,102,16,20,84,68,55,25,78,70,29],right:[30,68,31,32,93,70,38,39,96,41,112,43,97,45,2,47,48,10,11,12,14,15,16,17,18,19,101,20,64,21,78,23,82,61,86,25,54,65],old:[23,38,39,37,70,29,40,45,103,98,94,25,11,56,15,16,97],getargumentlist:16,unabashedli:65,attornei:25,olt:70,paralleltarget:65,dominatorset:76,txt:[68
 ,60,53,20,93,10,79,25,26,105,24],sparcsubtarget:52,bottom:[30,59,82,52,0,32,20,76,13,4,70,58,80],undisturb:68,lto_module_get_num_symbol:90,stringsort:68,subclass:[84,101,52,40,74,54,20,91,76,68,16,6,18,115],cassert:[68,8],armv7l:34,topleveltarget:65,op_begin:16,condit:[30,68,32,94,3,4,70,39,8,41,54,43,97,45,2,47,49,13,14,15,16,17,18,19,52,102,20,76,23,59,60,107,84,86,90],foo:[91,0,68,70,66,8,41,5,97,46,47,48,10,12,13,84,16,18,19,101,102,20,103,55,22,78,79,58,107,29,61,40,54,28,115],"0f00000000":8,armv7a:[9,93],sensibl:16,leftr:32,egregi:25,tablegen:[23,64,60,52,37,84,9,81,93,69,21,99,26,65,114,28,6,115],bindex:52,emitt:[52,47,98,21,13,114,70,115],image_scn_mem_lock:108,llvmanalysi:50,true_branch_weight:3,slightli:[68,16,45,2,48,76,73,12,14,15,70],xor64rr:84,dw_tag_array_typ:103,selectiondagisel:21,basenam:103,expandop:64,mbb:[84,52],creativ:52,mcinstlow:84,wrap:[71,23,68,102,43,41,70,20,91,46,103,25,111,54,4,16,17,18,19],msp430:[23,84,87],data32bitsdirect:52,suffici:[23,102,61,101,3
 0,74,5,20,40,43,86,83,29,70,73,65,27,115,16,17,49],support:[72,30,91,0,32,1,77,46,115,3,54,69,4,68,98,70,6,37,38,39,84,8,41,5,43,97,45,2,47,48,10,11,49,73,12,13,14,15,16,17,18,19,51,100,52,102,74,101,20,64,103,76,21,22,78,56,110,93,96,23,60,90,24,40,86,87,62,63,25,88,50,111,107,26,65,105,28,29,89],sub_rr:115,happi:[15,45,50],avail:[30,68,0,31,33,1,67,93,94,4,98,70,6,37,101,40,41,43,97,2,47,48,10,49,12,13,16,17,19,100,52,74,20,75,103,55,76,113,77,80,23,81,60,107,29,84,86,87,62,25,88,26,65,115],width:[38,68,111,0,74,70,84,86,11,49,78,16],cpprefer:16,distsubdir:65,icon:82,use_back:16,headach:31,"0x2413bc":76,fpga:84,offer:[74,29,91,16,86],refcount:74,dllstorageclass:[70,111],multiprocessor:[74,76],reserveresourc:84,profdata:[66,70,67,109],mymod:65,insidi:68,reiter:70,handili:68,fermi:84,dump_valu:[12,13,14,15,19],rerun:65,isexternalsymbol:52,adopt:[4,25,68,84],mirror:[23,74,2,47,13,14],proven:[30,45,110,49,15,70],exist:[30,91,73,1,46,94,68,4,70,6,37,38,39,84,40,41,5,97,45,2,47,48,10,11
 ,92,13,14,15,16,50,19,52,53,74,99,64,103,76,113,77,22,102,96,23,107,24,61,86,63,88,111,26,65,105,29,115],flagsflat:91,nvvmreflect:8,ericsson:70,build_phi:[13,14,15],bswap:[64,70],floor:[70,0],role:[68,31,32,103,74,54,28,18],finalizeobject:[71,39,45,2,47,48],presum:70,smell:16,roll:[68,101],mri:84,legitim:68,notif:40,intend:[30,4,70,71,37,64,96,40,5,44,46,49,16,52,74,20,23,60,90,24,84,86,25,88,107,65,27,28],createargumentalloca:[39,45],intens:[16,49,0],intent:[96,70,29,84,45,25,90,78,15,28],preverifi:30,keycol:69,dyn_switch:68,"1s100000s11010s10100s1111s1010s110s11s1":16,cumemcpyhtod:8,pre_stor:84,time:[30,61,0,31,32,33,1,77,46,115,94,35,68,70,6,71,37,7,39,84,8,41,5,43,9,2,47,48,10,49,45,12,13,14,15,16,17,50,19,52,53,74,90,20,75,64,103,76,113,21,22,110,79,80,55,93,58,96,23,59,60,73,83,24,40,86,87,91,62,63,25,88,111,26,65,105,28,29,99],push:[74,84,68,39,83],image_file_dl:108,corpu:24,breadth:[80,43,17],nearbyint:[70,0],chain:[23,59,84,52,30,70,29,1,45,40,103,76,35,21,90,32,4,15,16],pt
 rtoint:[70,49,102],sparctargetmachin:52,osi:97,aptr:70,const_nul:[13,14,15],image_sym_type_short:108,decid:[64,91,0,73,20,61,45,2,48,76,78,54,12,14,15,70,18,103],hold:[30,32,70,6,71,39,41,54,43,45,2,47,48,10,12,13,14,15,16,18,19,52,74,20,103,76,23,24,84,50,26,115],pem:24,decim:[96,20,91,22,70,115],worth:[83,68,16,34,101],x08:108,decis:[68,0,83,84,48,25,78,107,12,70],x03:108,uadd:70,macho:[71,84],oversight:25,x04:108,painlessli:20,uint32_max:103,cudevicecomputecap:8,vmcore:[60,20,16,64],fullest:68,exact:[30,68,53,74,16,20,103,86,76,90,26,70,33],numlin:66,solver:84,tear:107,unsupport:[84,52,31,1,86,93,10,35],team:[50,93],cooki:[70,16],prevent:[30,68,0,73,4,70,39,40,41,5,97,45,10,15,16,19,74,20,103,76,29,85,25,88,65],feat_inlineasm:84,dcmake_cxx_flag:9,sign:[38,68,104,82,52,102,70,20,84,25,11,49,111,90,16,29,115],heavyweight:16,scev:[30,40],relocat:[71,80,52],llvm_lit_tools_dir:[35,60],regex_t:24,filenameindex1:66,lazili:[12,90,16,111,48],currenc:[12,84,25,48],thecu:39,merge_bb:[13,14,
 15],current:[72,30,91,31,32,1,77,46,35,3,69,4,68,70,6,71,37,38,39,84,8,41,5,43,97,9,2,47,48,10,11,49,45,12,13,14,15,16,17,18,19,66,52,102,74,54,20,64,103,76,113,21,22,78,80,110,93,96,23,60,73,107,24,40,85,86,87,62,63,25,88,50,111,112,26,65,28,29,115],image_scn_cnt_cod:108,i256:70,objdir:[23,87,65],oeq:70,intraprocedur:83,adc64rr:6,cudevicegetnam:8,dropdown:82,autogener:25,live_begin:74,modif:[39,96,52,16,20,103,83,76,3,90,32,70],splice:[70,16],address:[30,84,0,32,67,70,6,71,37,38,8,45,46,48,11,49,73,12,15,16,52,102,74,20,103,55,76,110,78,79,60,82,107,24,40,85,86,62,25,88,111,29,115],along:[30,84,32,68,69,70,71,38,101,8,41,43,48,11,49,12,16,17,19,52,74,103,76,110,23,60,61,85,86,111,105],ffast:0,cur_var:15,volumin:16,commentstr:52,queue:[76,16,52],throughput:49,replaceinstwithvalu:16,safepoint:[37,29,73],mipsel:[23,87],commonli:[68,52,74,16,111,70],ourselv:[68,103,8],ipc:4,ipa:59,love:16,"2ap3":22,pentium:[23,52],prefer:[86,82,52,40,31,70,24,43,68,34,17,113,25,49,32,79,4,107,16,6],ipo
 :[32,59],src2:[84,6,115],regalloc:[76,80,77,84],src1:[84,6,115],cttz:70,instal:[31,45,33,34,35,6,64,39,8,41,54,97,9,2,47,48,12,13,14,15,16,18,19,100,76,113,23,60,24,87,62,63,50,26,65,29],llvm_lib_search_path:23,anothercategori:20,virtreg:84,image_sym_class_nul:108,abbrevid:111,scope:[68,73,70,39,40,41,45,2,47,13,14,15,83,19,74,103,76,21,16,29,91,25,111,107,114,115],tightli:[39,41,54,45,2,47,48,68,12,13,14,15,70,18,19],"66ghz":113,peopl:[37,38,68,82,102,43,31,20,84,64,93,76,25,11,4,70,17,97],claus:[84,25,70,107],refrain:[70,93],enhanc:[37,38,39,41,73,45,2,47,48,76,25,11,68,12,13,14,15,114,19],visual:[23,68,60,52,37,30,70,84,47,35,22,13,5,16],dualiti:29,linkmodul:65,langref:[64,86],easiest:[23,38,52,86,93,76,11,105],behalf:[25,82],b_ctor_bas:5,subel:70,descriptor:[111,39,88,103,52],valuet:16,whatev:[30,60,102,40,70,20,91,4,5],problemat:68,encapsul:[68,101,56],recycl:84,setrecordnam:111,optnon:70,r11b:6,r11d:6,"0x00001c00":84,fpu:[29,9,34],legalizetyp:84,parameter:115,r11w:6,remap:[71,
 84],motohiro:84,getsigjmp_buftyp:68,dw_apple_property_gett:103,spot:[30,24,93],mrm4m:52,mrm4r:52,succ:68,isfloatingpointti:16,date:[23,96,40,31,29,47,93,35,87,65,13,83,115],fucompi:84,data:[30,91,84,67,94,68,4,70,6,71,64,39,8,102,45,2,47,48,49,12,13,14,15,16,66,52,53,74,20,103,76,110,22,78,57,59,83,29,40,86,109,88,111,107,65,90,24,115],codes:6,stress:[24,68,42,67],rc2:[31,93],indexloc:16,disable_auto_depend:65,stdio:[23,63,35,13,12,4,14,15,90],stdin:[39,10,12,13,14,15,5,18,19],mangl:[110,68,25,70,103],fp4:[6,115],sandbox:[31,9],fp6:[6,115],fp1:[6,115],fp0:[6,115],fp3:[6,115],fp2:[6,115],callabl:[68,8,41,16,70,19],iftmp:[39,45,2,47,13,14,15],untest:31,operand_type_list_end:52,my_funct:8,llvm_library_vis:74,tta:29,numbyt:88,x86retflag:115,overhaul:93,thumb:[4,25,68,84,101],image_sym_class_block:108,denser:[14,2],precedecnc:[39,45,2],instantli:16,"__stack_chk_guard":70,jit:[84,33,35,68,98,70,37,38,39,8,41,112,43,97,45,2,47,48,11,12,13,14,15,16,17,18,19,51,100,52,74,80,23,60,83,29,61,87
 ,62,88,26,65],cmptype:32,canonicalis:78,image_sym_class_end_of_struct:108,outli:107,smarter:20,isbinaryop:[39,45,2],"0x00000147":103,inpredsens:69,therebi:[20,88],"0x00000140":103,mcode:22,getanalysi:76,revers:[30,59,0,5,102,78,16],llvm_src_dir:34,separ:[84,33,94,68,4,70,8,5,9,46,10,50,52,102,74,20,103,76,21,110,58,23,60,91,86,87,25,88,18,111,54,26,65,105,90,115],dwarf2:39,image_sym_class_end_of_funct:108,complextyp:108,updat:[30,32,93,70,71,38,39,96,40,41,5,97,45,2,47,48,11,73,12,13,14,15,16,101,74,20,64,103,76,78,23,60,82,107,29,84,87,88,54,90],compil:[30,61,107,0,31,32,33,77,34,67,93,94,35,68,4,70,6,66,37,38,39,104,84,8,41,5,43,97,9,2,47,48,10,11,45,12,13,14,15,16,17,18,19,100,52,102,74,54,20,64,103,76,113,21,78,80,110,23,59,60,73,83,24,40,87,62,25,88,50,111,112,26,65,90,29],argvalu:[20,98],registertarget:52,switchinst:[30,3],"__has_attribut":21,blx:22,movsx64rr32:84,"0x100":103,toolchain:[23,29,84,60,68],blk:16,"0x1c2":22,libxxx:9,getschedclass:52,pseudocod:52,million:[70,16],re
 movefrompar:16,crazier:[13,47],micromip:29,"byte":[36,70,66,64,96,40,12,13,14,15,16,18,19,52,102,103,55,78,24,84,85,86,88,111,29],subregist:[88,52],reusabl:84,departur:65,clangattrvisitor:21,ifuzz:24,sysconfdir:65,modest:68,recov:[16,107,5,70,88],neglect:33,arraytyp:16,oper:[30,91,0,32,68,3,4,70,6,66,38,39,104,84,8,41,54,43,97,45,2,47,48,11,49,73,12,13,14,15,16,17,18,19,51,52,53,64,103,76,21,78,80,102,96,60,107,29,40,86,55,77,111,65,28,115],onc:[91,107,31,32,33,1,93,94,35,68,4,70,6,71,37,7,84,40,41,112,97,45,47,48,11,73,12,13,15,16,18,19,52,102,74,90,20,75,38,76,23,59,60,83,24,61,87,63,25,54,111,64,65,105,28,29,115],iaddroff:84,coveragemappingdataforfunctionrecord1:66,coveragemappingdataforfunctionrecord0:66,submit:[23,82,37,61,93,25,83],symmetri:10,subtarget:[84,21,52,114],open:[68,32,35,4,70,37,112,97,12,13,14,15,19,101,103,59,60,29,84,25,88,65,105,115],lexicograph:[32,68],addtmp4:[41,19],f89:8,f88:8,convent:[68,32,70,39,104,52,8,41,97,46,73,16,19,101,103,21,82,29,84,88,111,105],b
 ite:97,f80:70,enable_optim:[62,23,93,87,65],optlevel:20,draft:[23,103,86],addtmp1:[12,48],lnt:[10,31,33,9],getsubtarget:52,conveni:[30,68,1,70,66,38,8,97,2,47,10,11,13,14,16,50,101,20,23,29,84,25,115],goldberg91:74,usenamedoperandt:52,fma:[84,8,70,0],programat:[14,84,2],artifact:[32,102],"__apple_namespac":103,llvm_parallel_compile_job:60,third:[91,32,33,93,68,70,66,38,39,41,11,73,16,50,19,52,102,74,20,103,55,76,23,107,84,25,88,111],rival:16,rzi:8,param2:16,param1:16,"0x12345678":103,sai:[38,39,101,96,33,43,41,5,20,84,105,25,11,65,69,4,102,73,16,17,19],nicer:[20,39,16,91],argument:[72,30,84,32,33,1,67,46,35,68,36,69,70,6,71,38,39,101,40,41,5,97,45,2,47,48,10,11,49,73,12,13,14,15,16,18,19,66,100,52,102,74,54,20,64,103,76,110,78,80,23,60,107,29,61,85,63,88,112,65,114,28,115],second_tru:70,sar:84,saw:[76,13,90,47],entrytoken:84,notw:5,xxxgenregisterinfo:52,destroi:[84,52,16,91,46,76,107,70,97],note:[30,61,54,32,33,1,34,67,93,68,36,69,4,98,70,6,71,37,38,39,104,84,8,41,112,43,102,9,2,47,
 48,10,11,49,45,12,13,14,15,16,17,18,19,52,101,74,90,20,64,103,76,77,22,78,56,96,23,59,60,82,73,83,24,40,86,87,25,88,50,111,107,26,65,28,29,115],denomin:68,take:[30,91,107,31,32,101,1,77,46,35,68,36,69,70,71,7,39,84,8,41,5,43,97,45,2,47,48,11,73,12,13,14,15,16,17,18,19,52,102,74,90,20,75,38,103,76,21,78,56,80,92,23,106,83,24,40,108,86,87,109,63,25,88,54,111,64,65,105,28,115],llvmcreatesimplemcjitmemorymanag:88,funcion:8,printer:[30,52,74,84,21,26,27],buffer:[70,38,39,41,54,45,2,47,48,11,12,13,14,15,16,17,18,19,103,107,24,90,29],fcc_ug:52,compress:[23,60,111,36,65,16],insertel:[70,5,78],abus:16,homepag:[23,35],allevi:[70,20,84,16],"_function_nam":22,drive:[26,34],axi:0,mcjit:[71,23,39,37,29,45,2,47,48,49,98],merit:68,identifierstr:[39,41,54,43,45,2,47,48],log2:[70,0],cclib:[14,15],objptr:70,slot:[30,52,73,84,45,46,88,85,36,15,70],xmm:[70,5,52],xmo:104,mergefunct:[32,37],activ:[37,68,52,40,74,16,51,84,46,76,25,88,107,70],v2size:40,freebsd5:84,dw_tag_imported_declar:103,v16f32:70,flagsc
 pu2:91,flagscpu1:91,clang:[68,0,31,45,1,34,93,35,3,98,70,6,66,37,38,39,8,41,5,97,9,2,47,48,10,11,12,15,16,50,102,77,103,21,23,59,60,82,107,24,61,86,87,63,25,54,26,65,90,29],"import":[30,91,0,31,32,1,34,93,35,68,69,70,37,38,39,40,41,54,44,2,47,48,11,49,12,13,14,84,16,18,19,52,74,20,103,76,78,23,60,83,29,61,86,25,88,111],requir:[30,91,31,32,1,34,46,94,35,68,69,4,54,70,71,38,39,104,84,8,41,5,43,97,9,2,47,48,10,11,49,45,12,13,14,15,16,17,18,19,66,52,53,74,101,20,64,76,21,78,102,93,96,23,60,73,83,24,40,86,63,25,88,50,111,107,26,65,90,29,115],embedd:29,prime:[39,41,54,45,2,47,48,12,13,14,15,18,19],borrow:70,specialsquar:101,getframes:74,openorcreatefileforwrit:4,xmax:[14,2],clenumvalend:20,where:[30,91,31,32,33,1,68,93,94,35,3,101,70,6,71,64,39,84,8,41,5,43,97,45,47,48,10,49,73,12,13,15,16,17,18,19,66,52,102,74,20,75,103,76,78,56,58,96,23,60,82,83,29,61,86,87,63,25,50,111,107,26,65,114,28],sinbio:24,deadlin:25,postdom:30,dw_at_apple_property_sett:103,arglist:70,xxxtrait:91,clangcommenthtm
 ltagsproperti:21,x86targetmachin:84,x24:108,build_mul:[12,13,14,15,19],getindex:52,spars:[23,64,59,30,84,16],screen:31,secnam:22,opval:52,sparc:[23,104,52,84,86,87,76,115],uncondition:[84,39,22,40],genericvalu:[12,13,14,15],eflag:[6,115],extern_weak:[70,111],kleckner:29,mani:[30,61,0,31,45,33,46,35,68,101,4,70,97,38,84,8,41,5,43,44,9,2,47,48,10,11,73,12,13,14,15,16,17,18,19,52,102,74,20,64,103,76,78,58,23,82,83,24,40,86,91,88,111,54,26,65,29],summaris:78,qhelpgener:60,dw_at_mips_linkage_nam:103,unistd:4,sccp:[30,59],sentinel:16,constant:[30,84,32,68,36,70,66,64,39,8,41,97,45,2,47,48,49,73,12,16,19,52,74,20,103,76,22,23,59,29,40,86,88,111],boat:68,curs:[112,1],printstar:[13,47],fib:[30,39,43,45,47,13,15,17],add16mr:6,pluginfilenam:80,ismod:115,parseifexpr:[39,45,2,47],inst_begin:16,add16mi:6,reflex:32,constantfoldcal:64,symobl:22,thousand:30,resolut:[90,2],release_15:23,ppcisellow:64,call_site_num:107,former:[73,84,86,18,54],combine1:84,combine2:84,emitalign:74,columnstart:66,polli:6
 0,view_function_cfg:13,test_exec_root:1,codgen:19,lto_module_get_symbol_attribut:90,canon:[70,16,103,78,30],blah:[20,68],pthread:70,ascii:[39,96,41,54,43,45,2,47,48,103,111,12,13,14,15,70,17,18,19],binari:[30,68,31,32,93,35,70,71,7,39,95,8,41,54,43,97,9,2,47,48,11,45,12,13,14,15,16,17,18,19,66,100,52,74,20,75,38,103,21,22,79,104,92,23,60,106,83,29,84,108,62,63,25,111,24,115],devcount:8,tutori:[32,5,37,38,39,8,41,54,43,45,2,47,48,11,12,13,14,15,17,18,19,51,20,29,65],immutableset:16,srem:[84,70],sreg:8,unhandl:107,irread:60,"0x1603020":98,getfunct:[39,41,45,2,47,48,76,74,16],extern:[30,68,31,32,33,34,70,71,38,39,96,8,41,54,43,45,2,47,48,10,11,49,73,12,13,14,15,16,17,18,19,51,52,20,103,76,110,78,80,24,84,62,63,111,90,29],defi:70,sret:[70,111],defm:[28,6,52,115],fnname:[39,41,54,45,2,47,48],dw_form_ref_udata:103,clobber:[84,70,115,40],dereferenc:[70,102,16,49,30],runtimedyldmacho:71,noencod:84,resp:[70,16],rest:[23,39,74,5,24,84,45,103,105,25,90,54,111,32,4,15,70,18,16],checkcudaerror:8
 ,fmadd:84,gdb:[37,38,52,84,103,98,76,63,11,16],unmaintain:6,invalid:[30,68,1,71,39,40,41,54,45,2,47,48,12,13,14,15,16,18,19,52,102,20,75,103,76,59,107,24,91,109,88],smallvector:[39,16],loadable_modul:[10,65,76,74],cond_fals:[15,45],r13w:6,"__builtin_trap":24,ghostli:16,"__imp_":70,littl:[30,68,32,34,4,70,38,39,41,54,43,97,45,2,47,48,11,73,14,15,16,17,18,19,52,102,74,20,103,76,78,23,29,84,111,65,105],instrument:[66,23,30,24,102,109,94,70,29],r13d:6,r13b:6,exercis:[10,38,11],dwarfdebug:103,featurev8deprec:52,uncal:68,disubprogram:39,mrm2m:[52,115],around:[30,68,32,93,4,70,38,39,40,54,97,46,47,11,13,16,52,102,20,103,76,56,23,86,25,26],libm:[12,41,48,70,19],libc:[23,38,68,70,25,11,16],unveil:[43,17],libz:70,traffic:[45,15,16],dispatch:[88,16,18,54],llvm_lib:60,world:[66,23,38,74,43,103,76,35,11,105,70,17],mrm2r:[52,115],find_program:60,intel:[60,0,104,9,10,77,80,70],"__gxx_personality_v0":[107,70],integ:[84,0,32,68,36,5,66,64,96,8,41,70,10,72,49,73,16,19,52,102,74,20,103,58,107,29,91,11
 1,28,115],timepassesisen:20,inter:[4,25,59,40],manag:[31,93,35,71,38,40,112,97,45,11,15,83,52,102,74,76,23,59,82,16,88,113],typestack:64,attrlist:21,a64:78,handshak:24,pushf:84,pred_iter:16,constitut:[10,16,111,78],pod:68,stryjewski:30,seterrorstr:[39,45,2,47,48],"0x000000000059c583":98,definit:[30,84,32,93,68,36,69,70,6,37,38,39,41,5,43,44,45,2,47,48,11,12,13,14,15,16,17,18,19,52,20,64,103,76,21,78,55,59,90,61,86,110,88,111,54,26,65,114,28,115],exim:24,parseextern:[39,41,54,45,2,47,48],evolv:90,noop:70,nonintuit:37,notabl:[23,60,102,16,29,84,87,70],ddd:96,pointnum:74,power:[30,34,46,70,6,104,40,41,54,43,45,2,47,48,99,12,13,14,15,16,17,18,19,20,82,29,84,90],isloopinvari:16,blockaddress:70,image_sym_type_union:108,n1984:68,n1987:68,ispic:52,standpoint:16,clangattrimpl:21,isset:20,mingw32msvc:84,lock:[76,70,16,86],spiffygrep:20,gplv3:63,aco:40,acm:[74,84],printmethod:52,compuat:59,act:[30,68,32,84,103,70,58,16],libtool:[23,97,65],industri:37,rebuild:[23,97,88,87,65],specialfp:115,srcl
 oc:70,effici:[30,68,4,70,37,40,54,97,46,48,10,12,16,18,101,74,103,55,76,21,23,29,84,25,111,27,115],surviv:[107,18,54],homeless:16,asymptomat:112,setinsertpoint:[39,41,45,2,47,48],hex:[91,70],movsx64rr16:84,clear_cach:70,kaleidoscop:[51,38,39,43,41,32,29,45,2,47,48,11,54,12,13,14,15,16,17,18,19],verbatim:[20,52],thedoclist:91,mantissa:70,conclud:[13,14,2,47],bundl:84,htpasswd:25,createjit:71,clenumv:20,epilog:[84,52],conclus:[51,38,39,32,43,45,11,54,15,17,18],ifunequ:70,pull:[23,68,86],tripl:[71,23,39,52,8,84,9,103,87,10,77,111,80,70],dirti:68,rage:36,agrep:33,inaccuraci:70,emitprologu:52,gcolumn:0,puls:24,basenamesourc:65,uid:96,creat:[30,84,0,31,32,33,1,77,46,94,35,68,4,70,6,71,37,38,39,96,8,41,54,97,9,2,47,48,11,99,45,12,13,14,15,16,17,18,19,51,100,52,102,74,20,75,103,55,76,21,78,56,115,93,23,60,82,73,90,24,91,87,25,88,50,107,113,65,27,105,28,66],certain:[1,70,66,64,96,40,5,45,48,12,15,16,20,76,22,78,23,29,84,62,88,65,115],numregion:66,getnamedoperandidx:52,creal:[14,2],movsx32rr8
 :84,googl:82,discrimin:[84,68,103,101],collector:[38,59,74,73,97,11,111,70],emphas:[29,68,105],collis:[68,41,16,29,103,70],writabl:103,freestand:70,of_list:[12,13,14,15,18,19],benchspec:33,numexpress:66,spiffysh:20,allowsanysmalls:16,mask:[84,52,74,5,91,68,21,56,70],shadowlist:52,llvm_shutdown:16,tricki:[74,76,68,86],mimic:68,createuitofp:[39,41,45,2,47,48],mass:58,prealloc:16,cpp:[68,0,32,4,98,5,64,39,8,41,54,97,45,2,47,48,10,100,52,74,20,103,76,21,23,60,24,84,87,65],cpu:[91,52,32,24,1,9,34,76,77,111,56,80,70,29],consider:[23,84,73,24,91,46,103,78,99,4,16,6],illustr:[43,41,70,20,45,103,48,76,90,78,54,12,15,16,17,18,19],labeltyp:16,scc:[76,30,59],dw_at_apple_properti:103,mno:29,fntree:32,astcontext:68,rewrit:[30,59,101,52,73,45,68,15],add16ri:6,incap:[38,11,111],add16rm:6,dsl:[6,99],tail:[30,38,111,8,28,84,103,11,70,32,5,115],add16rr:6,norm:[65,28,115],type_code_funct:111,getframeinfo:[84,52],"102kb":20,hard:[91,32,34,68,4,70,6,39,96,43,97,9,2,49,45,14,15,83,17,50,99,24,84,62,25],gc
 ov_prefix_strip:94,candid:[31,70,93],element_typ:[12,13,14,15,19],attr0:111,attr1:111,ia64:104,strang:[68,33,97,45,78,15],condition:1,quux:68,pedant:60,sane:[29,86,60,17,43],small:[68,32,33,93,36,4,70,66,37,39,8,112,43,10,49,16,17,101,102,74,20,103,76,80,83,24,84,109,25,88,111,26,29],release_xi:93,dsa:59,mount:23,"__image_info":70,sync:[23,29,91,86,8],past:[39,82,52,102,16,68,2,25,73,14,70,115],pass:[30,61,107,31,32,33,1,67,46,54,69,98,70,6,71,37,38,39,84,8,41,5,44,45,2,47,48,10,11,49,73,12,13,14,15,16,97,18,19,52,102,74,101,20,75,64,103,76,77,22,78,56,80,55,93,58,23,60,83,24,40,85,86,87,63,25,88,50,112,26,65,27,90,29],howev:[68,0,73,33,46,35,69,4,70,6,71,38,96,40,97,45,2,47,48,10,11,12,13,14,15,16,102,74,20,103,76,22,78,23,83,29,84,85,86,62,63,25,88,111,26,65,105],suboptim:29,enter_subblock:111,trick:[37,38,25,101,70,43,9,21,11,45,15,16,17],deleg:[107,86],xor:[30,84,52,8,16,0,70],registerregalloc:76,clock:[76,70],section:[30,84,0,32,33,1,108,67,93,68,4,70,71,38,39,96,40,101,54,102,
 48,11,49,73,12,16,18,66,52,53,74,20,75,103,76,21,22,78,89,79,80,57,23,60,107,29,61,85,86,25,88,111,26,65,27,105,115],delet:[30,84,32,68,70,39,96,8,41,5,97,45,2,47,48,12,13,14,15,16,19,103,76,23,83,24,40,63],abbrevi:[68,111,36],succinct:1,letlist:28,method:[91,32,33,68,101,4,70,71,64,84,40,41,5,45,46,47,48,12,13,15,16,19,52,102,74,20,103,76,21,56,59,83,61,88,54],contrast:[101,41,107,84,76,19],hasn:[76,16,102],full:[30,91,32,46,68,98,70,38,39,84,8,41,54,43,97,9,2,47,48,10,11,45,12,13,14,15,16,17,18,19,100,103,110,79,93,23,105,60,82,40,86,87,25,50,26,65,114],hash:[23,38,40,70,91,103,25,11,32,16],vtabl:[68,5,103,55],unmodifi:73,tailcal:84,blocknam:111,inher:[97,16],ineffici:[0,84,45,111,15,16],dw_tag_arg_vari:[39,103],islvalu:68,simpleproject:60,myownp3sett:103,shufflevector:[70,5,78],prior:[66,23,68,107,20,84,46,76,111,26,70],lto_module_get_symbol_nam:90,pick:[84,60,52,102,61,9,48,68,78,12,80,16],action:[64,68,52,74,16,84,76,3,107,65,70],narrowaddr:70,token_prec:[12,13,14,15,18,19],via
 :[30,73,4,70,6,71,39,9,98,10,99,16,75,76,21,22,79,23,82,107,29,84,87,63,88,65,90],depart:[68,96],dw_tag_namespac:103,ifcond:[39,45,2,47,13,14,15],vim:[23,105,6,65],memrr:52,image_sym_class_member_of_union:108,ifcont:[39,45,2,47,13,14,15],unbias:58,decrement:107,select:[30,84,33,1,35,68,69,70,6,71,64,8,45,15,16,52,102,20,76,21,78,110,23,59,60,82,83,91,87,25,107,65,115],x44:108,llvm_doxygen_qch_filenam:60,targetselect:[39,45,2,47,48],objectivec:70,isconst:[16,111],more:[30,61,107,0,31,32,33,1,34,46,115,94,35,68,36,101,4,70,6,66,37,38,39,84,8,41,5,43,97,9,2,47,48,10,11,49,45,12,13,14,15,16,17,18,19,52,102,74,54,20,75,64,103,76,113,21,56,57,96,23,59,60,82,83,24,40,85,86,87,91,62,25,88,50,111,112,26,65,27,105,90,29,99],isintegerti:16,door:101,tester:[37,33,1,67,93,25],hundr:49,f3_2:52,type_code_metadata:111,zeroext:[29,70,111],addcom:74,webkit:[88,70],multiset:16,compani:25,cach:[71,30,39,60,40,16,29,84,34,103,76,88,86,70],uint64:88,llvm_on_unix:4,enable_if:101,at_apple_properti:103,x86c
 allingconv:52,minnum:70,isnullvalu:32,returntyp:70,learn:[23,38,68,82,70,29,45,105,11,32,15,16],cmpinst:16,legalizedag:64,bogu:76,scan:[76,38,84,74,32,77,1,68,48,10,21,11,12,80],challeng:[73,14,68,2],registr:[104,52,74,97,98,76],accept:[23,68,82,101,8,5,20,97,93,63,35,25,22,70,32,72,27,16,28,115],pessim:30,x86instrinfo:52,v_reg:84,huge:[23,68,10,21,25,6],llvmgrep:23,readobj:[23,57,67],attrpchwrit:21,feat_objectwrit:84,clangxx:10,appenduniqu:70,simpl:[30,91,0,32,33,1,35,68,4,70,66,38,39,84,8,41,5,43,45,2,47,48,10,11,73,12,13,14,15,16,17,18,19,51,52,102,74,20,64,103,76,77,78,80,110,58,23,60,83,24,40,86,25,111,54,26,27,29,115],fptoui:70,loophead:[70,2,47],plant:76,referenc:[32,70,39,41,54,45,2,47,48,12,13,14,15,16,18,19,52,20,103,55,110,59,90,29,63,111,28],spillalign:52,variant:[76,30,52,16,20,10,26,88,13,12,4,14,15,5,17,18,19],unsound:73,plane:[14,2],dllvm_use_sanit:24,maywritetomemori:[16,86],thought:[41,73,84,70,28,19],circumst:[52,5,45,48,76,70,107,12,65,15,16],github:[51,24,82],ar
 canist:[37,82],author:[59,101,32,84,68,25,49,70,97],imm_eq0:6,atan2:[43,17],nvidia:[84,8],returns_signed_char:70,constitu:[13,47],ith:16,trade:[83,16],i386:[79,84],paper:[37,84,68,104],vec2:[70,16],pane:82,vec1:[70,16],bou_unset:20,nifti:[76,13,38,11,47],alli:70,gcov:94,hexinteg:28,superflu:102,slight:22,targetselectiondag:[64,84,52],image_sym_type_void:108,argsv:[39,41,45,2,47,48],cond_next:[15,45],instruct:[72,30,61,0,32,68,3,36,69,70,6,37,38,39,104,84,8,41,5,97,45,46,47,48,10,11,49,42,73,12,13,15,16,19,52,102,74,64,103,76,21,78,80,96,23,59,60,82,83,24,40,85,86,87,63,77,88,111,107,65,27,114,29,115],authent:[113,104],achiev:[60,70,86,90,69,4,16],tokcodefrag:28,lto_module_is_object_file_in_memory_for_target:90,found:[30,61,107,0,31,84,93,35,36,69,4,70,37,39,96,8,41,5,45,2,10,14,15,16,50,19,52,74,20,103,76,23,60,106,83,29,40,87,91,25,112,65,90],gettermin:16,errata:104,quesion:32,clangattrparsedattrimpl:21,"0b000011":52,monoton:[70,86,93],procedur:[59,104,43,32,20,93,78,16,17,50],real
 li:[30,68,33,35,70,38,39,41,43,97,45,2,47,48,10,11,12,13,14,15,16,17,19,102,20,64,103,23,60,86,25,65,105,28,115],loweralloc:76,getcalleesavedreg:52,reduct:[30,68,0,112,67,80,70],reconstitut:70,ftp:23,massiv:[65,21,44],ftz:8,stackframes:74,research:[37,33,64,103],getbasicblock:84,x86genregisterinfo:[84,52],occurr:[20,5,111],ftl:[88,70],loopbb:[39,45,2,47],isfirstclasstyp:32,distoth:65,mrm0r:52,numabbrevop:111,believ:[68,70,2,47,48,25,12,13,14,16],"__cxa_begin_catch":107,instrmap:[69,52],mrm0m:52,fnptrval:70,xxxend:16,struggl:23,amper:34,testament:[43,17],ge_missing_jmp_buf:68,new_then_bb:[13,14,15],major:[66,23,84,52,30,5,29,40,45,62,93,10,25,70,32,68,15,16,6,97],instprint:21,dw_at_high_pc:103,curesult:8,unprofit:30,number:[30,84,0,54,32,33,1,68,93,94,3,36,98,70,6,66,37,38,39,96,40,41,5,43,97,9,2,47,48,10,11,49,45,12,13,14,15,16,17,18,19,100,52,102,74,90,20,64,103,76,78,56,58,23,59,60,82,73,83,29,91,85,87,105,62,25,88,50,111,107,26,65,114,28,115],distchecktop:65,obj_root:[23,87],horr
 ibl:68,dw_at_low_pc:103,"0xxxxxxxxx":103,exponenti:[30,20,70],checkpoint:107,unrecogniz:110,functionast:[39,41,54,45,2,47,48],illeg:[30,84,102,8,16,20,0,73,70,24,97],dfa:[84,21,114],fptr:[39,45,2,47,48],relationship:[52,74,32,103,76,70,73,69,4,5,16],bio_writ:24,dagarglist:28,consult:[23,59,96,37,29,76,35,65],aad:84,llvm_svn_rw:98,tokstr:28,seamlessli:90,powi:70,reus:[84,103,76,25,88,70],arrang:[76,30,101,20,84,10,70],comput:[30,84,73,68,36,70,66,38,39,104,8,41,43,97,45,2,47,48,11,49,12,13,14,15,16,17,19,52,102,74,76,58,83,29,40,88,113],packag:[23,60,37,31,9,34,93,62,65,58,50],returns_twic:70,flto:63,equival:[30,68,32,70,38,8,72,11,16,102,74,20,22,78,80,107,29,84,86,111,65,28,115],odd:[20,25,68,29,61],self:[66,30,97,82,74,16,29,84,2,48,76,54,111,32,12,14,70,33,18],also:[0,1,2,4,5,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26,28,29,30,31,32,33,34,35,36,37,38,39,40,41,54,43,45,46,47,48,50,52,56,59,60,91,62,63,64,65,69,70,66,72,73,74,76,77,78,79,80,83,84,86,87,88,90,68,92,93,
 94,95,96,97,102,103,82,107,110,111,112,105,115],without:[30,68,107,0,32,93,94,4,98,70,6,66,39,96,5,43,97,45,2,47,48,10,12,13,14,15,16,17,18,100,52,102,74,54,20,103,76,21,78,56,80,58,23,59,60,83,29,84,86,87,62,63,25,88,50,111,112,65,27,105,90],ex2:8,selp:8,ptrc:8,coff:[104,84,108,22,111,70],ptra:8,pipelin:[76,30,39,52,8,45,2,47,48,10,111,36,12,13,14,15,70],unset_vari:65,rhs_val:[12,13,14,15,19],step_val:[13,14,15],plai:[38,32,43,76,11,28,17],plan:[23,97,8,74,84,46,76,25,16,6],exn:70,alu32_rr:69,"0x14c":108,cover:[68,32,35,70,66,5,43,2,10,49,14,17,52,102,20,103,76,23,24,84,25,88,113,105],ext:78,abnorm:[4,49],exp:[3,70,0],microsoft:[37,68,60,20,84,46,35,22,113,104,70,29],pubnam:103,gold:[23,37,29,84,34,63],getsymbolnam:52,xcode:[23,60,98],gcmetadaprint:74,session:[105,16,98],tracevalu:30,ugt:70,impact:[68,74,16,103,49,70],addrri:52,writer:[37,64,84,104,52,74,32,44,86,76,111,114,70,97],solut:[37,38,97,60,32,20,84,45,103,86,76,11,78,15,16,24],mergereturn:30,baseregisterinfo:21,llvm_execu
 tionengin:[12,13,14,15,29],factor:[68,0,16,84,70,6,115],bernstein:103,i64imm:52,llvm_obj_dir:97,agg3:70,agg2:70,mainten:[69,25,90],bitmap:111,n1757:68,f2_1:52,synthet:52,f2_2:52,synthes:[12,64,103,48],"__stack_chk_fail":70,machinememoperand:86,coerce_offset0:5,link_compon:[65,50],set:[30,91,31,32,33,1,77,34,46,94,35,68,69,4,70,6,71,37,64,39,104,84,8,41,112,43,97,9,2,47,48,10,45,12,13,14,15,16,17,18,19,66,52,101,74,90,20,103,55,76,113,21,78,80,110,93,96,23,60,82,73,83,24,40,87,62,63,25,88,50,111,54,26,65,114,28,29,115],image_sym_class_member_of_enum:108,seq:108,creator:[76,23,60],overwhelm:[43,17],organ:[37,68,32,33,103,48,10,12,107,73,26,4,50],startup:[23,68,8,1,62,70],see:[30,61,0,31,32,33,1,77,35,3,36,101,4,68,70,6,37,7,39,95,84,8,41,5,97,9,2,47,48,10,11,45,12,13,14,15,16,105,18,19,52,53,74,54,20,75,38,103,76,113,21,78,89,79,80,102,110,58,96,92,23,59,60,82,73,112,24,40,86,87,83,25,88,50,111,64,26,65,27,114,29,115],sed:[23,97,65],sec:70,sea:[104,72],overboard:68,analog:[74,70,115,1
 6,73],module_code_tripl:111,reglist:52,parsenumberexpr:[39,41,54,45,2,47,48],lto_codegen_cr:90,topmost:74,mymaptyp:91,subdir:65,documentlisttrait:91,mappingtrait:91,thrive:37,signatur:[96,73,29,84,76,78,36,70],machineoperand:[84,52],javascript:[70,38,11,88],libnam:[76,65,100],myocamlbuild:[12,13,14,15,19],disallow:[102,73,20,88,26,70],nohup:31,dividend:[84,70],proj_src_dir:65,closur:[26,38,11],last:[68,0,73,1,93,101,70,39,96,41,5,43,2,10,14,16,19,52,20,76,107,84,25,111,105,28,115],operarand:3,"0xh":70,whole:[30,68,32,33,70,64,96,54,9,47,48,10,12,13,16,18,74,76,56,24,84,25,26],lower16:22,sink:[30,20,40],load:[30,61,32,1,5,68,70,71,39,84,8,112,44,45,98,10,49,73,15,16,52,53,74,20,75,103,76,77,78,80,102,59,60,83,29,40,86,88,111,26,65,27,90],episod:[13,47],nakatani:84,schedul:[23,52,5,29,84,34,93,76,21,73,80,16],dw_tag_namelist:103,hollow:91,lex:[39,43,12,13,14,15,28,17,18,19],functionpass:[30,52,40,74,76,16],"0x100000f24":79,boolean_property_nam:26,worthless:68,shadowbyt:88,devic:[7,95,
 106,8,92,75,34],perpetu:25,"0xf":115,devis:50,firm:65,gettokpreced:[39,41,54,45,2,47,48],fire:[68,83],func:[66,7,70,29,76,12,13,14,15,16,18,19],registerpass:76,rdtsc:70,uncertain:68,straight:[40,41,32,43,84,54,56,4,115,16,17,18,19],erron:[23,20],histor:[10,68,70,86,102],durat:[76,84,40],passmanag:[71,39,20,45,2,47,48,76,12,13,14,15],error:[30,61,91,31,84,1,77,93,68,36,4,70,6,7,39,95,96,8,41,5,43,97,45,2,47,48,10,11,92,12,13,14,15,16,17,18,19,100,52,74,54,20,75,38,76,21,22,89,79,80,23,60,106,107,24,40,86,87,63,25,50,112,65,114,90,29,115],dvariabl:60,v1size:40,real:[23,68,52,8,5,20,40,43,2,103,24,70,14,16,6],pound:[65,91],reg2mem:30,binutil:[113,23,104,9,63],genregisternam:84,miscommun:25,inst_invok:111,chase:61,i29:70,decor:103,irrelev:[102,40],initializerconst:70,i20:70,i24:70,x64:[113,23,5],funni:[15,45],decod:[30,16,103,21,111,70,115],sparclite86x:52,built_sourc:65,foldingset:16,bitread:26,predreg:69,dw_at_declar:103,stack:[30,84,73,68,70,37,38,39,40,43,45,46,11,49,15,16,17,52,74,
 103,76,22,23,59,107,29,91,85,88,27,28],recent:[23,31,107,24,91,25,70],call32r:115,eleg:[38,54,47,48,11,12,13,18],rdi:[88,6],dw_apple_property_readwrit:103,llvm_unreach:[32,68],person:[91,107,29,61,105,70],parse_prototyp:[12,13,14,15,18,19],expens:[30,68,52,32,20,86,76,107,16],call32m:115,llvm_tablegen:60,always_inlin:30,crosscompil:[84,9],else_v:[13,14,15],immutablepass:[76,40],debug_level:20,simd:[80,77,70,0],numshadowbyt:88,sidebar:93,lfoo:84,smooshlab:37,eager:16,input:[30,91,0,84,1,94,36,69,70,6,97,7,39,95,8,41,5,43,44,45,2,47,48,10,11,92,12,13,15,83,17,19,52,54,20,75,38,103,76,21,79,80,57,110,23,59,24,40,108,109,77,112,65,114,90,115],transpar:[64,68,82,102,16,20,90],subfield:115,intuit:70,dw_tag_ptr_to_member_typ:103,"0x00000048c979":24,formal:[16,103,32,70,6,115],sgi:16,todefin:21,atomicexpand:86,ivar:103,stylist:68,threadsaf:74,image_sym_type_nul:108,parse_toplevel:[12,13,14,15,18,19],ii32:115,x86framelow:84,moduleid:[10,41,19],encount:[70,110,84,16,52],image_file_debug_strip
 :108,sampl:[66,39,8,41,54,20,108,98,74,35,50,69,24,18,19],sight:[15,45],itanium_abi_tripl:10,attrvisitor:21,instcount:30,libssl:24,"_bool":[15,45],p5i8:8,foreign:[97,60],recognit:29,llvm_obj_root:[10,65,33,50],xxxgendagisel:52,agreement:25,prerequisit:[76,52],wget:[23,24],indirectbrinst:3,materi:32,codeemittergen:21,image_sym_type_long:108,condbranch:52,oneormor:20,getinsertblock:[39,45,2,47],putchard:[38,39,41,45,2,47,48,11,12,13,14,15],primarili:[23,7,44,30,74,46,24,1,2,53,34,26,14,84,16,57,115],result_float:73,seamless:63,xxxinstrformat:52,requires_rtti:62,contributor:25,pcre:24,occupi:[70,96],span:[66,76,68,6],textual:[59,77,84,48,10,21,25,12,27,115,6,97],custom:[30,91,33,68,5,6,37,64,70,97,99,16,52,102,74,20,21,60,29,84,112,26],createcondbr:[39,45,2,47],suit:[23,64,84,60,31,32,29,1,9,103,87,93,10,35,25,107,65,16,33,97],parse_arg:[12,13,14,15,18,19],expound:103,subgraph:30,atop:74,lint:30,nodupl:70,atoi:70,link:[30,61,31,32,67,93,35,68,70,66,37,38,84,8,41,112,43,9,2,48,10,11,12,
 13,14,15,16,17,50,19,100,52,74,20,75,103,55,76,110,22,96,23,81,59,60,82,106,83,29,40,85,86,87,62,63,25,26,65,105,90,24],atom:[37,68,30,5,29,103,86,49,70,16],line:[91,107,0,31,84,33,1,94,35,68,36,98,70,6,66,37,7,39,95,96,8,41,5,43,97,45,2,47,48,10,11,92,12,13,14,15,16,17,18,19,52,74,54,20,75,38,103,76,77,56,79,80,57,110,23,59,60,82,106,83,24,61,105,86,87,109,62,63,25,50,112,26,65,114,29,115],talli:33,clangattrspel:21,simplif:[76,30,83],cin:97,intim:68,hex8:91,"0xffffffff":111,fdiv:70,doc:[23,64,39,60,37,112,29,91,9,87,93,104,105],impl:[76,30,16],debugtrap:70,parser:[70,38,39,41,54,43,97,45,2,47,48,11,12,13,14,15,17,18,19,51,20,21,23,24,84,26,114],cxx_fuzzer_token:24,"char":[68,0,98,70,66,39,96,8,41,54,45,2,47,48,12,13,14,15,16,17,18,19,52,102,20,103,76,24,40,90],insertvalu:70,gcfunctioninfo:74,doe:[30,61,91,32,33,1,46,94,35,68,101,4,98,70,97,71,38,39,95,84,8,41,5,43,44,45,2,47,48,10,11,49,73,12,13,14,15,16,17,18,19,52,102,74,90,20,64,103,76,110,22,56,93,96,23,60,83,24,40,85,86,87,63,
 25,88,50,111,107,65,27,28,115],linkonceodrlinkag:16,tok_unari:[39,45,2],intrepid:[54,18],xxxcodeemitt:52,ud2a:84,kwalifi:108,scrape:1,download_prerequisit:23,disp32:84,isnotduplic:6,issiz:16,caml:[51,17,18],lang:20,mayalia:40,lane:[70,78],land:[73,25,70,46,107],x86codeemitt:52,algorithm:[30,68,32,70,38,40,54,44,45,47,11,13,15,16,18,52,74,20,21,107,29,84],agg:70,getregisterinfo:[84,52],fresh:[23,24,65],hello:[66,23,43,76,35,70,17,115],mustalia:40,llvmcontext:[39,41,16,45,2,47,48,70],code:[0,1,2,4,5,6,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,55,23,24,25,26,28,29,30,31,32,33,34,35,37,38,39,40,41,112,43,45,46,47,48,49,50,51,52,103,56,59,60,61,62,63,65,66,91,67,70,71,72,73,74,76,77,78,79,80,83,84,85,86,87,88,89,90,68,93,94,96,97,98,101,102,64,105,82,107,110,111,54,114,115],partial:[30,59,0,16,91,114,88,84,70],resultv:70,scratch:[70,29,16,52],setcc:[84,16],globallisttyp:16,printimplicitdef:52,young:16,send:[23,7,84,95,82,37,31,32,29,61,77,86,93,10,25,49,92,113,114,76,105],tr1:16,sens:[3
 8,68,60,96,102,40,41,70,20,84,46,103,11,86,16,97,19],getprocesstripl:39,sent:[37,25,82,92,93,77,73,109],unzip:[31,23],flagscpumask:91,clearresourc:84,registeredarg:74,tri:[30,60,52,32,43,84,83,76,105,70,17],bsd4:96,setconvertact:52,magic:[23,96,16,103,2,111,14,70],dname:20,complic:[23,64,68,101,52,0,74,24,46,86,10,35],trc:84,scalabl:40,tre:30,blockquot:111,fewer:[74,30,73],"__llvm_covmap":66,race:[70,16,86],build_uitofp:[12,13,14,15,19],udiv:70,vehicl:68,use_s:16,monospac:105,natur:[30,68,31,4,5,41,70,45,47,13,15,16,19,101,102,74,20,103,76,23,107,91,86,25,105,90,115],odr:70,proj_obj_dir:65,psubu:10,rauw:[32,29,59,16],instnam:30,ueq:[45,15,70],index:[84,73,93,70,66,37,39,96,40,49,16,52,102,74,20,103,21,22,78,56,23,107,91,109,88,111,65],twine:16,targetregisterclass:[84,52],asmwrit:[74,64,21],getanalysisusag:[76,40],henceforth:[85,70],paramti:111,image_scn_align_64byt:108,dyn_cast_or_nul:16,lea:[84,6],leb:66,targetregisterinfo:[84,52],len:70,short_enum:70,sparctargetlow:52,rglob:7,let:
 [61,32,33,69,70,6,66,38,39,84,8,41,5,43,45,2,47,48,11,73,12,13,14,15,16,17,18,19,52,102,101,20,103,76,82,90,29,40,62,54,113,105,28,115],ubuntu:[23,9,34],ptx30:84,ptx31:84,great:[68,74,43,84,2,76,25,65,14,16,17],survei:104,dllvm_enable_doxygen:60,technolog:[90,38,11,29],rdx:[88,6],flagshollow:91,global_end:16,ifloc:39,qualifi:[68,102,84,103,93,70,97],somemap:68,fake:80,sgt:70,pf1:32,pf0:32,sgn:70,llvm_enable_cxx1i:60,sge:70,movsx32rr16:84,"__________":16,getnumparam:16,eltti:[39,111],zip:[23,65],commun:[71,37,90,59,8,70,40,68,93,76,25,88,49,4,98,16,97],my_fmad:8,doubl:[30,84,32,35,70,38,39,104,101,41,5,43,45,2,47,48,11,12,13,14,15,16,17,18,19,52,20,103,91,111,54,65,115],upgrad:[23,97,25,103,53],next:[68,31,32,93,35,69,70,71,39,101,41,5,43,45,2,47,48,10,12,13,14,15,16,17,18,19,52,102,74,54,20,103,76,23,83,29,111,107,90],doubt:[105,101],n2439:68,commut:[30,84,52,40],fpregsclass:52,comparison:[30,101,0,31,70,102,2,86,3,54,32,14,73,16,18],gladli:[23,35],firstcondit:16,bunzip2:23,objectsl
 o:65,uvari:60,get_instrinfo_operand_enum:52,folder:[23,60],devmajor:8,intregssuperregclass:52,scatter:[103,0],gc_root:73,statepoint_token:73,dw_form_data4:103,n2431:68,weaker:70,dw_form_data1:103,dw_form_data2:103,process:[30,91,0,31,32,34,93,68,69,4,98,70,6,71,37,38,96,5,43,48,10,11,12,84,16,17,18,66,52,74,54,20,103,76,110,58,23,83,24,61,86,87,25,107,26,65,90,29],optioncategori:20,preformat:105,high:[30,84,0,93,68,4,70,71,37,38,96,8,97,45,98,10,11,49,15,16,50,66,52,102,74,64,103,107,40,25,111,115],pictur:[41,32,102,19],fprintf:[39,41,54,45,2,47,48],streamer:84,dw_ate_signed_char:103,msvc:[22,29,84,16,68],adc32mi8:6,visitsrl:64,delai:[32,16],infeas:59,allocainst:[68,16,45,39,15,70],stand:[76,68,16,84,10,25,54,70,18],afl:24,overridden:[32,70,52,40],singular:68,add32ri:6,xc3:108,loc0:88,loc1:88,xc7:108,xc4:108,x86registerinfo:[84,52],addri:52,dw_at_apple_property_attribut:103,dw_tag_class_typ:103,alloc:[91,73,68,70,71,38,40,45,46,48,11,49,12,15,16,52,102,74,76,77,22,80,23,107,84,85,88
 ],essenti:[52,74,16,75,86,111,32,28],sdiv:[84,70],counter:[66,83,24,86,109,72,70,16],robot:37,element:[28,64,91,111,52,8,16,0,68,40,103,21,55,78,32,30,102,84,70,105,115],issu:[91,84,1,34,93,68,38,8,43,45,47,48,10,11,49,12,13,15,16,17,20,103,76,21,22,78,23,29,40,87,25],liveintervalanalysi:84,unaccept:25,allow:[30,91,107,0,32,1,68,108,46,94,3,101,4,98,70,6,71,37,38,39,84,8,41,5,43,97,45,2,47,48,10,11,49,73,12,13,14,15,16,17,18,19,66,52,102,74,54,20,99,64,103,76,77,22,78,56,55,96,23,60,82,90,24,40,85,86,62,25,88,111,112,26,65,27,28,29,115],retval:[39,41,45,2,47,48,70],stepexpr:[39,15,45,2,47],movl:[88,5],decltyp:68,fstrict:70,movi:68,move:[30,68,73,93,70,6,38,39,96,40,97,45,2,47,48,11,99,13,74,76,23,81,29,84,86,25,88],stacksav:[70,46],llvmsetdisasmopt:27,movz:78,movw:22,oprofil:[62,60],ofstream:20,movq:88,perfect:[25,78],define_abbrev:111,disambigu:[49,40],chosen:[84,68,1,70,78],interlink:29,infrastructur:[76,23,64,84,37,74,16,29,1,68,40,103,10,25,83,113,70,50],cond_tru:[15,45],lastins
 t:52,decad:6,therefor:[66,30,84,102,8,74,16,20,91,86,76,25,88,78,27,70],python:[23,38,31,29,1,9,10,74,35,11,28],initializenativetarget:[39,45,2,47,48],overal:[82,102,74,107,84,47,21,25,13,70],innermost:0,facilit:[68,16,91,103,25,70,50],add32rr:6,fcc_val:52,anyth:[30,68,35,6,41,97,47,48,12,13,16,19,101,103,77,80,23,84,86,87,25,88],hasexternallinkag:16,xvjf:23,truth:[13,70,47],"0b111":115,llvminitializesparcasmprint:52,compute_xx:8,idxmask:70,subset:[38,102,8,70,33,1,40,103,10,25,11,16],denseset:16,"0x7fffffffe040":98,bump:[74,85,16],"0x400":103,lsampl:50,"static":[30,91,32,67,46,68,70,71,64,39,101,40,41,112,43,97,9,2,47,48,49,45,12,84,16,50,19,52,102,74,20,103,76,21,80,23,59,73,83,29,61,86,77,54,65,90,24],differ:[30,91,0,31,32,33,77,93,35,68,36,69,4,70,6,71,37,38,39,104,84,8,41,5,44,45,2,47,48,10,11,49,42,73,12,13,14,15,16,97,19,66,52,101,74,90,20,64,103,76,21,22,78,56,102,58,23,60,82,83,24,40,87,25,88,111,107,65,28,29,115],unique_ptr:[39,45,2,47,48],variabl:[30,61,0,32,33,1,94,35,68
 ,36,70,71,7,39,84,8,41,5,43,97,45,2,47,48,10,11,49,73,12,13,14,15,16,17,18,19,51,52,102,74,20,38,103,76,22,55,96,23,59,60,29,40,85,86,87,91,63,88,50,111,54,65,115,28,66],matrix:[74,84],contigu:[70,16,103],myregalloc:76,tok_if:[39,45,2,47],tok_in:[39,45,2,47],memorysanit:70,shut:[68,52],initializepass:40,unpars:[54,1,18],tempt:[4,68,23],image_file_system:108,shortest:[32,28],shtest:1,spill:[73,84,88,52,80],could:[30,84,32,1,46,68,69,4,70,38,39,101,40,41,5,97,45,2,47,48,10,11,73,12,13,15,16,18,52,102,74,20,99,103,56,23,60,82,83,29,91,86,87,63,88,54,113,105,24,115],area:[68,31,107,84,45,10,74,25,78,4,15,70,97],scari:[38,11,17,43],length:[30,0,73,1,70,66,96,10,12,13,14,15,16,19,102,20,103,22,78,111,105,115],enforc:[68,74,5,20,84,86,88,70,16,115],outsid:[30,59,63,33,37,31,70,20,40,86,76,41,68,88,32,4,102,73,16,24,19],scare:25,spilt:84,softwar:[23,38,68,52,41,43,93,10,74,35,25,11,80,65,76,17],scene:16,add_pt:69,spaghetti:[43,17],selectiondagnod:[84,52],fcontext:39,owner:[39,96,84,45,2,47,
 48,25,93],stringswitch:21,add_pf:69,featurev9:52,sparcgensubtarget:52,licens:[68,97,93,76,63,25],system:[61,31,45,33,77,34,93,35,68,4,70,6,37,38,39,104,84,8,41,43,97,9,2,47,48,11,12,15,16,17,50,102,53,20,64,103,76,21,78,80,96,23,59,60,82,29,40,87,62,63,25,88,26,65,90,115],parse_oper:[14,15],gcse:[76,30,16],termin:[30,68,32,1,3,4,70,7,95,96,8,44,47,10,49,92,13,83,52,20,75,103,76,106,16,107,115],f_inlined_into_main:79,llvmgcc:65,returnindex:56,ldrex:86,gotcha:68,endexpr:[39,15,45,2,47],baseclasslist:28,"12x10":70,arrayref:16,haven:[76,33,68,70],datatyp:[20,84,16,17,43],steen:40,bother:[15,45],arg_end:16,framealloc:70,bitvalu:91,stricter:[5,86],f1f2:32,xxxregisterinfo:52,tdtag:21,getzextvalu:16,viewer:68,op_end:16,var_arg_function_typ:19,clearli:[68,25,88],optimis:12,mdstring:[3,103],"0x00002200":103,disassembl:[23,37,92,29,84,67,35,21,36,26,27,114,70],tramp1:70,accuraci:[30,70],at_typ:103,nontempor:70,rvalu:68,type_of:[12,13,14,15,19],courtesi:25,griddim:8,poison4:70,poison3:70,poison
 2:70,incfil:65,setloadextact:52,ffi_include_dir:60,segment:[37,84,85,103,88],placement:[73,30,49,50,65],stronger:[70,16,86,73],parsevarexpr:[39,45],face:[76,4,68,21,85],isbranch:6,brew:16,linkonc:[23,8,70,22,111,16],fact:[68,70,38,96,40,41,97,45,2,48,11,49,12,14,15,16,101,102,20,76,23,59,107,84,25,26,28,115],movslq:88,dbn:23,borderlin:68,truedest:70,dbg:[30,39,83,29,103,70],module_code_deplib:111,rough:[115,28,86,102],trivial:[30,68,4,70,38,40,54,43,97,45,46,48,11,12,15,16,17,18,52,102,20,64,103,76,78,84,86],redirect:[10,112,39,93],isstor:84,getelementptr:[66,38,84,102,8,74,5,36,40,46,11,70,32,55,16,97],image_sym_class_argu:108,should:[30,61,91,31,32,33,1,77,34,93,94,35,3,69,4,68,70,6,71,37,64,39,84,8,41,112,43,97,9,46,47,48,10,99,45,12,13,54,15,16,17,18,19,52,101,74,90,20,75,103,76,113,21,78,56,80,102,58,96,23,105,60,82,73,83,24,40,86,87,62,63,25,88,50,111,107,26,65,27,114,28,29,115],jan:96,tape:23,create_funct:[12,13,14,15],opreand:16,nonzero:[111,115],hope:[68,74,32,29,62,25,73],
 meant:[66,28,23,31,32,75,35,37,65,105,70,115,16],insight:[66,70],notat:[23,96,28,20,91,103,70,115],familiar:[23,39,101,8,32,43,84,47,76,72,65,13,17],memcpi:[30,24,70,86,40],autom:[23,82,84,21,6,50],smash:70,isatleastreleas:86,symtab:16,machineconstantpool:84,reid:[4,29],dw_ate_sign:103,stuff:[39,115,84,20,91,45,47,48,76,105,12,13,15,16,33,97],booltmp:[39,41,45,2,47,48,12,13,14,15,19],inlni:79,comma:[23,20,91,47,87,13,27,70,115],type_code_arrai:111,unimport:[31,73],frame:[71,30,38,59,107,52,74,70,29,84,85,46,103,77,11,73,79,88,16],packet:[113,84,21,114],temporarili:[65,83],binary_nam:79,movt:22,polymorph:[88,16],wire:97,op_iter:16,fakesourc:65,compute_factori:98,verilog:29,live_iter:74,sectionmemorymanag:[71,39,45,2,47,48],unrecurs:[15,45,39],email:[23,38,59,82,37,86,25,11],superword:[59,0],dislik:25,linkonceanylinkag:16,memri:[84,52],endl:68,use_iter:16,doxygen:[23,39,60,37,41,87,35,68,65,16,19],scalaropt:100,valgrind:[10,112,29,1,61],sdtc:52,etc:[30,68,31,32,33,93,35,4,70,6,37,38,3
 9,40,41,5,43,97,45,2,47,48,11,12,13,14,15,16,17,18,19,52,102,74,54,64,103,76,21,56,23,60,82,24,84,86,62,25,111,112,65,115,90,89],"0fbf317200":8,vk_basicblock:68,preheader_bb:[13,14],position_at_end:[12,13,14,15,19],exprprec:[39,41,54,45,2,47,48],indici:111,distil:10,bininteg:28,rpcc:70,vptr:[70,16],llvm_external_:60,triniti:104,insuffici:[4,70,34,52,103],va_arg:70,immedi:[30,68,73,86,70,71,38,96,8,97,45,48,11,12,15,16,52,76,29,84,40,88,111,27,115],hex16:91,deliber:[68,88],image_sym_type_char:108,togeth:[30,68,0,32,33,70,66,38,96,40,41,5,43,2,47,10,11,13,14,16,17,18,19,74,54,20,75,103,76,110,78,58,106,83,24,84,109,25,112,26,115],allocationinst:16,sphinx_output_man:60,rbx:[84,6],dataflow:[45,15,70],cvt:8,reloc_absolute_dword:52,rbp:[84,6],llvm_tools_binary_dir:60,cvf:93,decreas:80,cbw:84,objmakefil:65,auxiliarydata:108,apfloat:[39,41,45,2,47,48,19],site:[30,40,74,16,29,1,46,55,10,35,107,88,73,70],sn_map:32,uglygep:102,archiv:[23,96,37,24,67,63,25,26,65,110,90,50],mybuilddir:60,incom:[
 52,70,84,45,47,25,13,14,15,16],surprisingli:[23,54,48,49,12,18],greater:[30,68,111,52,8,74,32,84,3,78,36,102,70],mutat:[30,39,74,24,45,2,68,14,15,16],referenti:30,basicblocklisttyp:16,lex_com:[12,13,14,15,17,18,19],dbgopt:103,preserve_mostcc:[70,111],phi:[30,39,0,84,45,2,47,68,111,36,13,14,15,70],sadd:70,expans:[66,84,28,52,56],upon:[71,97,52,74,16,75,103,65,70,50],foldmemoryoperand:[84,52],expand:[66,64,91,52,115,5,56,114,10,68,49,36,32,65,57,84,70,6,97],off:[68,70,6,38,39,96,8,41,43,45,2,47,48,10,11,12,13,14,15,16,17,19,60,83,84,62,25],mention:[37,68,60,111,101,73,16,20,84,85,103,72,78,32,26,70,29,115],diversifi:24,argnam:[39,41,54,20,45,2,47,48],exampl:[0,1,2,3,4,5,6,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,55,23,24,25,26,27,29,30,31,32,33,34,35,38,39,40,41,54,43,44,45,46,47,48,50,52,103,56,58,59,60,61,62,63,65,91,69,70,66,73,74,75,76,78,79,83,84,86,87,88,89,90,68,97,98,100,101,102,64,82,107,111,112,113,105,115],command:[61,0,31,84,33,1,67,93,35,68,36,98,70,6,37,7,39,95,96,8,41
 ,5,43,97,45,2,47,48,10,92,12,13,14,15,16,17,18,19,52,54,20,75,76,113,21,56,79,80,57,110,23,60,82,106,83,40,87,109,63,77,88,112,26,65,114,90],svnup:23,filesystem:[1,9],outputfilenam:20,newest:22,paus:[74,40],xec:108,prepend:[94,16,103],web:[29,25,82],makefil:[23,100,61,60,52,37,41,90,33,53,87,10,74,26,65,84,76,97,50,19],blockfrequencyinfo:[37,58],exempt:68,target_opt:[23,87],nonnul:[70,49],nvt:52,globalopt:[76,30],dest:70,clangcommentnod:21,piec:[61,93,68,70,39,41,54,43,45,2,47,10,13,14,15,83,17,18,19,102,103,23,24,84,25,111,26,115],core2:10,five:[107,20,84,16],release_16:23,tick:96,xe8:108,recurr:30,desc:[76,20,52],addsdrm:115,resid:[111,8,74,24,103,76,78,70],emmc:34,type_code_vector:111,isus:84,objectbuff:71,byteswap:64,resiz:68,"0x29273623":103,captur:[70,38,39,41,5,45,2,47,48,10,11,12,13,14,15,83,18,19,54,20,103,84,88,111,64],vsx:29,main_loop:[12,13,14,15,18,19],build_exampl:65,i64:[52,8,5,84,103,88,78,73,102,70,6],emitglobaladdress:52,flush:[71,68,8,34,12,13,14,15,70,18,19],guar
 ante:[30,73,70,38,40,97,45,11,15,16,102,74,20,103,76,21,23,107,84,86,25,88,65],transport:29,"__syncthread":8,avoid:[68,31,32,34,4,70,6,39,101,40,45,46,10,49,15,16,52,102,74,103,76,78,23,83,24,84,25,88,111,90,29,115],image_sym_class_fil:108,mnemon:[84,52],arg_siz:[39,41,45,2,47,48,74,16],imaginari:103,barlist:68,multidimension:70,stage:[37,52,8,31,32,20,84,93,54,112,90,18],"0x4200":103,c_str:[39,8,41,54,20,45,2,47,48,16,43],interven:88,lld:[23,29,68,60],nullari:[54,18],uniquevector:16,dw_op_deref:103,x86_vectorcallcc:29,getbitwidth:16,handleextern:[39,41,54,45,2,47,48],dw_tag_base_typ:103,retcc_x86_32:52,takecallback:16,waterfal:113,mere:[30,102,41,73,35,70,19],merg:[30,0,31,32,93,70,66,37,39,40,41,5,45,2,47,48,12,13,14,15,16,18,19,103,60,84,109,25,54,90],behind:[37,84,8,5,61,103,76,68,70,56,69,16],createsubroutinetyp:39,relpo:96,valuesuffix:28,multidef:115,textfileread:68,ssl_filetype_pem:24,p4i8:8,mandel:[14,2],llvm_include_exampl:60,mdnode:[3,70,103],"function":[30,61,0,32,67,46,9
 4,68,36,69,4,98,70,97,71,37,7,39,84,8,41,5,43,44,45,2,47,48,11,49,73,12,13,14,15,16,17,18,19,66,52,102,74,101,20,75,38,103,76,21,78,56,79,110,58,96,23,59,60,109,83,24,40,85,86,87,91,62,63,107,88,54,111,64,26,65,27,90,29],reduc:[30,84,31,32,68,69,70,6,66,37,7,39,96,8,112,48,12,83,102,20,76,16,29,61,25],documentlist:91,getenv:4,dw_at_entry_pc:103,count:[30,0,33,94,5,16,66,64,96,40,54,10,83,18,52,74,20,103,70,56,107,109],inst_cal:111,data16bitsdirect:52,lookup_funct:[12,13,14,15,19],evidenc:102,localexec:[70,111],otherwis:[30,91,32,1,34,93,94,68,36,70,66,7,39,95,41,5,43,44,9,2,47,48,72,49,45,12,13,14,15,16,17,18,19,100,53,90,20,75,103,76,77,80,57,58,92,59,60,106,73,83,24,61,86,107,54,111,112,65,114,28,115],problem:[30,84,45,46,35,68,4,5,37,38,39,40,41,112,97,9,2,47,10,11,73,13,14,15,16,19,102,74,20,99,103,76,78,93,23,83,24,61,62,25],"int":[91,0,32,46,35,68,69,98,70,6,66,38,39,84,8,41,5,43,97,45,2,47,48,11,12,13,14,15,16,18,19,52,102,74,90,20,103,78,79,23,83,24,40,108,86,63,54,112,105,2
 8,115],rightli:65,ini:26,ind:39,insertdeclar:39,ing:[30,68,41,45,48,12,15,19],inc:[52,84,76,21,69,65],bzip2:[23,65],nonetheless:70,optsiz:[70,111],libcxx:31,lookup:[23,38,68,52,30,41,70,2,103,11,32,14,15,16,19],varieti:[68,34,38,104,96,40,41,2,47,48,11,12,13,14,16,19,74,103,23,59,107,29,84,86,88,111,26,28],getopt:20,liblzma:9,computearea:101,"0f3fb8aa3b":8,smallstr:16,defaultlib:35,emitsymbolattribut:84,fexist:32,in0:70,in1:[84,70],in2:84,"85c1f5":66,eof:[39,41,54,24,45,2,47,48,43],header_data:103,cumemfre:8,dumpabl:76,rabfik:96,configmaxtest:16,hashes_count:103,sourceloc:39,sm_20:[84,8],sm_21:84,untrust:25,child:[14,2,101],show_bug:24,rapid:25,"const":[91,32,46,68,70,66,64,39,101,8,41,54,45,2,47,48,16,52,74,20,103,76,24,84,40,90],lsda:107,r8b:6,r8d:6,deviat:[68,84,22],binoppreced:[39,41,54,45,2,47,48],thefunct:[39,41,45,2,47,48],r8w:6,rowfield:69,emploi:16,printnextinstruct:16,getpar:[45,39,16,2,47],glibcxx_3:23,type_code_numentri:111,llvm_enable_ffi:60,cmd:82,upload:82,defens:25,"
 0x2a":78,red:70,add_rr:115,add_char:[12,13,14,15,17,18,19],externally_initi:70,callcount:16,cmp:[70,84,16,30],abil:[64,75,84,43,74,70,20,91,45,2,47,103,98,27,13,14,15,16,17,50],soutbio:24,hork:115,mcstreamer:[74,84],consequ:[23,40,16,83,10,88,107,65,70],ilist:16,image_scn_mem_shar:108,llvmbuild:[26,37,53],scalarenumerationtrait:91,disk:[68,90,24,1,103,26,4,70],runfunctionasmain:98,loop_bb:[13,14,15],qux:70,topolog:5,told:68,ontwo:70,copysign:70,somefunc:[68,16],mcoperand:84,pred_end:16,clangattrspellinglistindex:21,myregisteralloc:76,optzn:[39,61,45,2,47,48,12,13,14,15],"0f7f800000":8,aka:[39,84,40,41,70,29,43,45,2,47,48,54,12,13,14,15,16,17,18,19],werror:63,dcmake_cxx_link_flag:23,idnam:[39,41,54,45,2,47,48],instr:[66,74,84,115,114],invas:[25,91],setgc:74,sspstrong:70,ftoi:52,total:[30,32,33,85,103,86,76,111,36,70,16],bra:8,highli:[74,16,24,84,45,49,15,70,50],bookkeep:[30,16],plot:[14,2],postincr:68,afterward:30,foster:[4,25],greedi:[84,20,77],simplifycfg:[30,15,45,97,112],setreg:8
 4,iscommut:6,llvm_enable_p:60,numberofauxsymbol:108,toolkit:[16,8],tblegen:21,armgenasmmatch:21,word:[68,101,52,41,16,20,84,103,58,74,97,111,107,70,24,19],insignific:[88,44,70],err:[76,24,16,8],restor:[39,52,85,84,45,2,47,46,88,111,107,13,14,15,70],next_prec:[12,13,14,15,18,19],work:[72,30,91,32,33,1,77,46,35,68,36,101,4,70,6,71,37,38,39,104,84,40,41,5,43,97,9,2,47,48,10,11,45,12,13,14,15,16,17,18,19,66,52,53,74,54,20,64,103,76,113,21,102,93,58,23,59,60,73,83,24,61,85,86,87,109,63,25,50,112,26,65,90,29],foo_ctor:46,respres:16,viewcfgonli:[16,47],unnam:[28,20,68,70,30],"16gb":113,novic:60,lexer:[51,38,39,43,41,54,24,45,2,47,48,11,64,12,13,14,15,17,18,19],autodetect:[80,77],u64:8,extractvalu:70,llvmcore:[31,50],liter:[68,70,39,96,41,54,43,45,2,47,48,12,13,14,15,16,17,18,19,20,111,27,28,115],unavail:[86,52],constantstruct:16,createinstructioncombiningpass:[39,45,2,47,48],str2:115,ordinari:[66,70],lexloc:39,fastisel:21,sever:[30,68,31,32,33,1,36,4,70,6,66,37,38,96,40,41,97,47,10,11,13,1
 6,50,19,52,74,20,64,103,76,21,56,23,60,106,83,24,84,87,109,111,107,65,90,115],verifi:[30,73,67,93,36,70,39,41,5,97,45,2,47,48,10,13,14,15,83,50,19,53,75,103,55,76,25,88,111,65,105],bindir:[65,100],ssl_set_bio:24,arcp:70,superreg:52,rebas:23,lad:20,chines:23,after:[30,91,107,32,33,34,46,94,68,101,4,54,70,6,71,38,39,84,8,41,5,97,9,2,47,48,10,11,45,12,13,14,15,16,18,19,66,52,102,74,90,20,75,103,76,21,78,80,93,58,96,92,23,60,73,83,40,86,87,25,88,50,111,112,113,65,27,105,28,115],hex32:91,lab:[113,37],law:68,arch:[23,96,31,93,77,79,80],demonstr:[66,52,41,16,29,48,12,70,19],sparccallingconv:52,domin:[30,68,23,74,16,45,76,15,70],opaqu:[30,78,73,111,70,16],lto_module_dispos:90,recompil:[40,29,47,88,78,13],icmpinst:16,buildslav:113,noitinerari:[6,52],order:[30,84,32,33,1,35,68,69,4,98,70,97,66,64,101,40,41,5,43,44,45,47,48,10,49,73,12,13,15,16,17,18,19,52,53,74,20,75,103,76,110,22,78,102,23,107,29,91,86,87,25,88,50,111,54,26,65,90,115],movhpd:5,ud2:84,diagnos:[76,44,0],use_camlp4:[12,13,14,15
 ,18,19],offici:[104,31,32,84,45,41,25,15],opnod:52,type_code_opaqu:111,pascal:70,noimm:6,getnexttoken:[39,41,54,45,2,47,48],flexibl:[76,84,101,16,20,1,2,67,10,70,26,14,5,6,115],getattribut:32,bytecod:[23,111,87],isellow:21,setoperationact:[84,52],induct:[30,23,41,0,45,40,47,76,13,15,19],them:[30,91,107,31,32,33,94,35,68,69,4,54,70,66,37,38,39,84,8,41,5,43,97,9,2,47,48,10,11,49,45,12,13,14,15,16,17,18,19,52,102,74,101,20,103,76,110,78,56,96,23,60,106,73,83,29,40,85,86,87,109,62,25,88,50,111,112,26,65,27,90,115],dw_apple_property_atom:103,thei:[30,84,107,0,31,32,33,1,34,93,68,36,69,4,70,6,66,37,38,101,96,40,41,5,44,45,46,47,48,10,11,49,73,12,13,15,16,97,18,19,52,102,74,54,20,75,103,76,21,78,80,110,23,59,83,24,91,86,87,25,88,50,111,112,26,65,27,29,115],fragment:[28,53,74,16,33,84,103,70,115],safe:[30,61,73,70,38,40,112,11,49,15,83,102,74,20,23,59,16,29,84,86,25,88,111],printccoperand:52,denorm:91,"break":[30,68,0,93,3,70,64,39,41,54,43,45,2,47,48,13,14,16,17,18,52,74,20,76,78,56,23,107
 ,29,84,62,25,27],bang:28,astread:21,selti:70,lifelong:37,stdarg:70,"__cxa_rethrow":107,sequentialtyp:16,monolith:[25,85],"0x000003cd":103,const_op_iter:16,network:29,visiticmpinst:83,misoptim:3,lib64:[23,60],forth:78,image_file_relocs_strip:108,multilin:[1,28,115],srcmakefil:65,registeralias:21,ms_abi_tripl:10,barrier:[8,74,73,29,86,70],multilib:9,standard:[30,84,0,73,1,35,68,36,4,70,6,37,7,39,95,96,8,41,5,43,97,45,2,47,48,10,104,11,49,92,12,13,14,15,16,17,18,19,52,74,54,20,75,38,103,76,77,22,78,79,80,57,110,23,106,107,29,40,86,87,109,25,111,112,65,114,90],nth:68,fixm:[23,52],debuglev:20,mvt:[84,52],angl:[91,68],zerodirect:52,regress:[23,68,31,83,33,1,87,93,10,25,65,5,50],cmpvalu:32,subtl:[38,102,54,24,47,48,11,12,13,18],boiler:20,render:[14,84,16,2],refin:[84,40],subreg:52,lto_code_gen_t:90,i48:70,setcondcodeact:52,llvm_build_32_bit:60,"0x00000000016677e0":98,ispredic:6,type_code_struct:111,image_file_bytes_reversed_hi:108,isalpha:[39,41,54,43,45,2,47,48],power8:29,john:68,"40th":[
 43,17],headerdata:103,getdatasect:74,inexact:70,tee:83,registerpasspars:76,gcmetadataprinterregistri:74,analyzebranch:52,hashdata:103,llvm_build_root:60,tokvarnam:28,provid:[30,91,32,33,1,68,34,35,3,36,101,4,98,70,71,37,38,39,84,8,41,112,102,45,2,47,48,11,49,73,12,72,15,16,18,19,66,52,53,74,20,75,103,76,113,21,79,96,23,59,60,107,29,40,86,87,25,88,50,111,54,26,65,27,90,115],cppflag:[65,50],minut:23,uint64_t:[32,91,16,58,56],hassse2:115,hassse3:115,emitfunctionstub:52,contenti:68,consumeaft:20,frontend:[66,29,44,46,86,10,49,26,70],n1737:68,manner:[66,23,52,102,73,84,86,87,107,70,16],strength:[37,84,30,16,20,43,86,49,70,17],recreat:[23,91,70],laden:[38,11],latter:[52,32,84,86,54,18],image_rel_amd64_secrel:22,"0x400528":79,postcal:74,llvm_doxygen_qhp_namespac:60,smul_lohi:84,attrdump:21,bruce:16,cumodul:8,dllvm_use_sanitize_coverag:24,lexic:[39,70,84,103,48,68,54,12,28,97,18],phase:[52,0,31,16,84,2,93,74,77,90,54,112,14,70,18],retcc_sparc32:52,passthru:70,valuerequir:20,instritinclass:6
 ,bracket:[68,107,91,103,26,70],notion:[68,101,29,84,103,47,48,76,25,12,13,70],uitofp:[41,45,47,13,15,70,19],confront:[49,102],md_prof:3,opposit:[65,59,96,91],freeform:20,overload:[64,101,52,8,16,2,76,73,65,14,70],buildbot:[10,37,1,113,93],identifi:[30,68,0,31,73,1,70,39,96,8,41,5,43,45,2,47,48,12,13,14,15,16,17,18,19,52,102,74,54,20,103,55,76,21,23,59,60,83,84,88,111,107,27,28],involv:[30,91,73,93,69,4,70,64,39,40,54,45,47,49,13,15,16,18,52,102,58,29,84,86,65],just:[30,91,31,32,33,1,94,35,68,36,101,4,70,6,97,66,38,39,84,40,41,5,43,44,9,2,47,48,10,11,45,12,13,14,15,16,17,18,19,52,102,20,103,76,21,78,80,110,58,96,23,82,73,83,24,61,85,86,87,63,25,88,50,111,54,26,65,105,29,115],the_funct:[12,13,14,15,19],"41m":20,sroa:59,baseopcod:[69,52],latenc:[80,84,70],callbackvh:16,govern:70,instlisttyp:16,predecessor:[30,70,84,47,49,13,16,58],showdebug:98,likewis:[74,23,70],tag_memb:103,dw_tag_compile_unit:103,llvm_include_tool:60,fp128:[32,70,111],didescriptor:[39,103],numregionarrai:66,lit_arg:1
 0,fomit:84,isosdarwin:39,emb:[70,38,11,111],cleanli:[76,68,25,70,93],ostream:[68,39,16],st_uid:96,cudevicegetcount:8,commandlin:[37,20],memorywithorigin:60,chapuni:37,dw_ate_float:[39,103],miscompil:[23,25,83,61,112],ssl_ctx_use_certificate_fil:24,awar:[23,68,101,40,5,20,84,103,86,25,26,102,16,24],sphinxquickstarttempl:[23,105,87],dicompileunit:39,unordered_set:16,awai:[30,68,101,5,29,103,17,76,58,90,16,43],getiniti:16,accord:[60,101,52,31,16,20,93,74,88,111,73,70,58],unsett:76,tst_code_entri:111,featurevi:52,preprocessor:[66,38,60,52,20,97,48,11,12,65],isjumptableindex:52,memorybuff:68,image_file_machine_armnt:108,cov:[66,94,24,67],ill:96,xmm0:[10,88,5,6,115],xmm1:[6,115],calltmp:[39,41,45,2,47,48,12,13,14,15,19],ilp:0,llvm_deleted_funct:68,themself:25,com:[23,68,51,24,25,16],col:39,con:[28,78],testcleanup:70,widen:[84,0],solari:23,resultti:70,excess:[80,24,77],getbasicblocklist:[45,39,16,2,47],permut:70,prologu:[39,52,74,29,85,111,70],wider:[64,86,102],guid:[30,31,33,67,93,35,70,6
 6,37,104,8,54,10,72,16,50,51,52,102,20,103,23,82,83,24,86,87,25,18,26,65],goodby:105,speak:[13,14,2,47],degener:[30,15,45],"__builtin_expect":3,macport:62,"__nvvm_reflect":8,debug_info:103,subscrib:[25,82],mallocbench:33,compatible_class:84,machineblockfrequencyinfo:58,hoist:[30,16,86,88,40],unclutt:4,binaryoper:[68,16],inhibit:70,ident:[30,68,32,70,96,40,5,45,47,48,10,12,13,14,15,16,17,18,19,74,103,78,84],aix:[84,104],gnu:[76,23,68,60,96,52,107,29,84,34,87,10,63,110,113,65,70,115],properti:[30,73,35,69,70,6,66,38,40,45,11,32,15,16,52,74,20,103,76,21,78,84,88,111,26],cxx_statu:68,aim:[66,68,112,29,83,25,78,4,70],scalarrepl:[30,15,45,86],pairwis:40,publicli:[16,103],aid:74,keytyp:103,opt:[30,61,0,33,67,35,68,8,112,97,45,47,48,10,12,13,15,16,20,75,76,23,83,29,40,25,65],xstep:[14,2],printabl:[70,96,52],conv:97,theexecutionengin:[39,45,2,47,48],image_sym_class_weak_extern:108,extractloop:30,uint32x2_t:78,cond:[39,52,97,45,2,47,13,14,15,70,58],int_of_float:[14,15],dw_tag_lexical_block:10
 3,dw_tag_enumer:103,old_val:[13,14,15],descent:[54,43,2,14,17,18],incorrectli:[41,43,68,19],perform:[30,84,0,31,32,33,1,34,93,68,4,70,71,64,96,8,41,97,45,46,10,11,49,73,72,15,16,50,19,52,102,74,20,75,38,103,76,77,78,23,59,60,83,29,40,86,87,25,88,107,26,65,90,115],descend:70,doxgyen:60,addintervalsforspil:84,fragil:[10,24,5],code_own:25,evil:[6,78],hand:[30,84,31,32,68,4,6,38,101,41,54,43,2,48,11,12,14,16,17,18,19,52,102,74,21,56,60,91,86],fuse:[30,70,80],use_llvm_scalar_opt:[12,13,14,15],disassembleremitt:21,operandv:[39,45,2],kept:[76,25,68,59,40],undesir:70,scenario:[10,83,97,16,86],incorpor:[84,16],thu:[30,84,32,68,70,66,40,41,54,97,2,47,48,10,49,73,12,13,14,15,16,18,19,74,20,103,76,58,82,83,61,25,111,107,65],hypothet:[76,32,84,16],whizbang:68,get_reginfo_target_desc:21,client:[68,71,37,101,40,45,48,12,15,16,52,53,74,20,103,55,76,60,29,84,25,88,111,26,27],thi:[0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26,27,28,29,30,31,32,33,34,35,36,37,38,39,40,41,112,4
 3,44,45,46,47,48,49,50,66,52,53,55,56,57,58,59,60,61,62,63,64,65,91,69,70,71,73,74,75,76,77,78,79,80,82,83,84,85,86,87,88,90,68,92,93,94,95,96,97,98,100,101,102,103,104,105,106,107,109,110,111,54,113,114,115],gettok:[39,41,54,43,45,2,47,48],clenumvaln:20,value_load:70,destsharedlib:65,mandelbrot:[14,43,2,17],stack_loc:84,ifdef:[66,4,20,11,38],sparctargetasminfo:52,opencl:[29,8],spread:30,board:[9,34],parse_primari:[12,13,14,15,18,19],relwithdebinfo:60,mayb:[38,21,11,24,64],stringwithspecialstr:103,fusion:70,fsin:[77,52],xdata:29,mip:[23,104,52,29,84,9,103,87,86,70],ppc32:[29,84],irbuilder_8h:[41,19],sectnam:20,entry_block:15,bucket_count:103,bpl:6,image_file_machine_ebc:108,openfil:68,prefixdata:111,negat:[14,2,111],percentag:36,cfrac:33,bork:[20,115],flatten:[84,70,0],bore:76,pos2:20,pos1:20,getmodulematchqu:52,colloqui:70,functioncompar:32,fpic:[29,60],loadregfromaddr:52,mandleconverg:[14,2],dopartialredundancyelimin:20,wunus:68,trunk:[23,37,24,84,103,93,10,35,25,33],peek:[12,13,1
 4,15,18,19],plu:[111,52,74,70,47,25,54,78,107,13,16,18],aggress:[30,59,23,74,54,0,40,47,103,68,13,84,70,18],memdep:[30,40],someclass:28,pose:[74,59],confer:[74,84],fastmath:8,repositori:[23,97,82,37,107,24,61,9,103,87,10,25],post:[30,37,84,25,80,70,50],obj:[100,31,33,74,35,77,79,70],literatur:84,image_scn_align_4byt:108,canonic:[16,84,5,30],s64:8,looppass:76,deltalinestart:66,nctaid:8,sames:70,curiou:32,xyz:[69,80,77],"float":[84,0,32,34,70,6,64,8,41,54,43,9,47,48,49,12,13,14,15,16,17,18,19,52,102,20,103,77,22,80,58,29,91,111],profession:25,bound:[52,8,74,16,91,103,46,73,102,70,115],emitinstruct:[84,52],unittestnametest:60,opportun:[30,52,0,48,12,70],accordingli:[69,74,16],wai:[30,61,107,0,31,32,33,46,35,68,101,98,70,6,66,38,39,84,8,41,5,43,97,9,2,47,48,10,11,49,45,12,13,14,15,16,17,18,19,52,102,74,54,20,103,76,21,56,79,93,96,23,73,83,24,40,86,91,25,88,50,111,112,26,65,29,115],callexprast:[39,41,54,45,2,47,48],type_code_half:111,n2764:68,instrprof_incr:70,lowest:[66,39,41,54,45,2,47
 ,48,68,78,86,12,13,14,15,70,18,19],asmwriternum:114,raw_ostream:[76,84,91,68],maxim:[80,43,17,111],argpromot:[30,40],"true":[30,91,32,68,3,69,70,6,39,84,8,101,112,9,47,10,12,13,14,15,16,19,52,102,74,20,103,76,79,80,23,29,40,86,63,28],reset:[24,111,115],absent:16,optimizationbit:20,legalizeop:64,returnaddress:70,maximum:[60,40,16,20,84,36,32,70,58],anew:103,absenc:[84,83],llvm_gc_root_chain:74,emit:[30,84,67,94,35,69,70,71,38,39,8,41,5,97,45,2,47,98,11,49,13,14,15,83,18,19,66,52,102,74,20,103,76,21,22,78,80,23,59,29,61,86,77,88,111,54,114,90],hotter:58,alongsid:111,wcover:68,thunderbird:25,noinlin:[98,70,111,56],xxxjitinfo:52,postscript:30,valuelist:28,encrypt:25,refactor:[29,15,45,59],instr0:32,instr1:32,instr2:32,entrypoint:[29,70],test:[30,91,31,32,33,1,77,34,67,93,35,68,70,66,37,7,45,84,40,5,97,9,47,48,10,55,42,12,13,15,16,50,101,53,107,20,64,103,76,21,57,23,60,83,29,61,87,63,25,112,26,65,114,24],shrink:84,realiti:93,xxxtargetasminfo:52,fpreg:52,"2acr96qjuqsym":25,dihead:103,sani
 tizercoverag:24,debugflag:[20,16],clang_cl:10,pathnam:[23,100,87],set_value_nam:[12,13,14,15,19],libgcc1:9,concept:[68,32,4,70,6,66,37,8,41,47,99,13,16,19,101,102,103,76,78,24,84,111,65,29],mayload:6,consum:[34,35,36,70,39,41,54,102,45,2,47,48,12,13,14,15,16,18,19,53,20,103,21,88,27],dw_tag_inlined_subroutin:103,supplement:104,value_typ:91,middl:[68,74,73,97,46,103],zone:70,graph:[30,33,70,39,41,45,2,47,48,12,13,14,15,83,19,52,76,58,23,59,16,29,84,114,115],certainli:[74,30,38,11,49],jvm:[38,11],"0x200":103,dootherth:68,munger_struct:102,fom:30,brows:[41,60,19],seemingli:52,dw_apple_property_readonli:103,avx1:10,avx2:10,administr:[113,93],aad8i8:84,elttypearrai:39,gui:[35,68,60],libthread_db:98,adc64ri8:6,gut:65,sparcinstrformat:52,usescustominsert:6,upper:[68,52,112,103,65,16],isvolatil:70,brave:[54,18],paramattr_code_entri:111,preservemost:70,cost:[38,68,52,0,32,84,62,90,11,70,107,69,16],build_fmul:19,cov_flag:24,f4ba70:66,after_bb:[13,14,15],gr16:84,appear:[66,30,44,96,52,40,70,20
 ,1,68,34,97,103,86,83,73,102,28,24,16],scaffold:[54,18],"23421e":70,constantarrai:16,uniform:[68,16],isoptim:103,va_list:70,image_sym_class_funct:108,defici:[43,99,6,17],gener:[0,1,2,3,4,5,6,8,10,11,12,13,14,15,16,17,18,19,20,21,22,55,23,24,25,26,27,28,29,30,31,32,33,35,36,37,38,39,40,41,42,43,45,46,47,48,49,50,51,52,54,103,59,60,61,65,66,91,67,70,71,72,73,74,75,76,77,78,80,83,84,85,86,87,88,90,68,93,94,96,97,98,99,101,102,64,105,82,107,109,111,112,114,115],inputcont:91,satisfi:[40,45,86,93,25,4,15],pcre_fuzz:24,vice:[10,16,86],roots_end:74,precursor:25,plotter:[14,2],hash_data_count:103,mach_universal_binari:79,behav:[68,40,107,61,86,70],myvar:102,triag:84,regardless:[30,7,68,60,106,74,92,75,45,103,62,35,95,15,70],extra:[23,68,60,102,30,31,16,20,61,85,107,10,3,49,111,32,70,24,115],stingi:16,stksizerecord:88,marker:[70,20,1,16,84],type_code_void:111,dagisel:21,llvm_on_xyz:4,regex:[20,5,33],prove:[30,40,32,33,46,49,70],nothrow:86,naddit:20,subvers:[23,97,82,29,61,87,93,10,35,25],live
 :[30,61,73,35,68,70,40,41,45,46,15,16,19,74,103,76,78,23,59,60,84,87,88,90],stackprotector:70,abs_fp64:6,lgtm:82,tlsv1_method:24,"0xl00000000000000004000900000000000":70,cxxabi:23,finit:[84,21,70],ctype:29,viewcfg:[16,47],geordi:37,iffals:70,dw_tag_express:103,logarithm:[32,16,111],graphic:[14,11,2,38],ibm:104,at_nam:103,canconstantfoldcallto:64,prepar:[71,30,82,37,31,32,24,102,9,107,65,70],focu:[84,90,105,0],cat:[23,74,20,10,79,24],ctfe:29,can:[0,1,2,4,5,6,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26,27,28,29,30,31,32,33,34,35,36,37,38,39,40,41,42,43,44,45,46,47,48,49,50,66,52,53,54,103,56,58,60,61,63,65,91,69,70,71,72,73,74,75,76,77,78,79,83,84,86,87,88,90,68,92,93,94,96,97,98,99,100,101,102,64,105,82,107,109,110,111,112,113,114,115],debug_symbol:[62,65],boilerpl:[101,74,20,48,21,12],heart:[73,65,53],underestim:70,basemulticlasslist:28,chip:[52,8,84,9,34,10,77,80],spu:52,topic:[51,38,68,60,43,24,11,105,16,17],abort:[83,68,70,115,107],spl:6,occur:[30,84,73,1,68,3,36,4,70,
 7,95,96,5,97,10,92,16,50,100,102,74,54,75,76,77,59,106,107,29,61,25,88,18,111,112,65,114,28],multipl:[30,84,0,32,33,46,94,68,4,70,6,71,7,39,96,40,41,5,2,47,48,10,73,12,13,14,16,18,19,66,52,102,20,103,76,113,21,22,79,110,58,23,24,91,86,87,25,88,50,111,54,26,28,29,115],image_sym_class_regist:108,ge_missing_sigjmp_buf:68,write:[30,91,32,33,35,68,36,4,70,6,37,7,39,95,96,8,5,43,97,46,47,48,10,11,73,12,13,84,16,17,50,51,52,53,74,20,75,38,103,76,21,79,102,92,23,105,60,106,24,40,86,87,25,88,114,29,115],regioninfo:30,"0x80":[103,96],x86instrss:52,product:[74,70,29,84,2,93,76,25,54,32,65,14,28,58,18],multiplicand:70,southern:104,targetmachin:[71,74,84,76,52],cours:[38,40,32,20,43,64,76,11,24,54,65,16,17,18],uint:77,drastic:4,lto_codegen_compil:90,breakag:25,voidtyp:16,newlin:[68,96,1,2,111,14,5],autotool:[63,87],copyphysreg:52,getcalledfunct:[74,16],assici:32,explicit:[68,32,70,38,39,8,97,45,2,47,48,11,12,13,14,15,16,101,102,74,20,103,76,22,23,59,84,86,25,26],is_base_of:101,objectimag:71,some
 what:[37,68,40,16,33,97,2,86,25,54,73,14,70,18],mapvector:16,ghc:[29,84,70],thread_loc:[84,70],approx:8,arch_nam:79,approv:[25,93],graphviz:[30,16],localtarget:65,svnrevert:23,cold:[70,49,58],still:[30,91,0,32,33,1,46,94,35,68,4,70,71,38,84,97,45,2,47,11,13,14,15,16,66,101,74,20,103,76,78,23,83,29,61,62,63,25,88,65,24],ieee:[77,70,49,96],dynam:[30,84,73,98,70,71,112,97,2,48,49,12,14,16,50,101,102,74,20,75,103,76,77,22,80,57,83,91,85,110,88,111],mypass:[76,16],conjunct:[53,31,65,4,70,115],precondit:[65,68],getoperand:[68,84,16,52],window:[76,23,68,60,37,70,20,84,2,47,46,10,35,104,22,29,13,113,4,16,24],addreg:84,curli:[10,70,68,16,115],val_success:70,llvm_doxygen_qhelpgenerator_path:60,has_asmprint:26,non:[30,91,107,31,32,1,68,36,69,70,71,7,95,84,8,101,5,43,44,45,46,47,48,10,11,49,73,12,13,15,16,17,18,66,100,52,53,74,90,20,75,38,103,76,77,80,102,96,92,23,60,106,112,24,40,86,87,83,63,25,88,54,111,64,114,28,29,115],evok:70,recal:[41,32,91,47,48,12,19],halv:64,half:[68,52,94,111,105,70],
 recap:78,superset:[70,96],nop:[88,29,70],discuss:[66,23,68,101,52,37,16,20,103,76,25,88,24,73,29,54,70,6,18,49],mybranch:23,introduct:[30,61,91,31,32,68,34,46,35,3,69,70,6,71,37,64,39,84,8,41,54,43,9,2,47,48,72,45,12,13,14,15,16,17,18,19,51,52,102,74,20,99,103,76,113,21,22,78,56,115,93,58,23,105,60,107,24,40,85,86,87,63,25,26,65,27,114,28,29,66],build_sub:[12,13,14,15,19],drop:[29,25,70,68,82],reg1024:84,reg1025:84,reg1026:84,reg1027:84,image_scn_align_1024byt:108,dw_tag_vari:103,domain:[38,52,74,84,11,99,70,6],replac:[30,73,94,4,70,96,8,45,10,49,32,15,16,52,74,20,110,56,23,59,60,90,29,84,86,63,25,107,28,24,115],arg2:[43,70,17],condmovfp:115,releasememori:76,contrib:23,backport:9,reallyhidden:20,year:[29,68,6],operand:[30,68,32,3,36,70,64,39,41,5,45,2,72,73,14,15,16,19,52,102,21,29,84,88,111,115],rl4:8,happen:[30,84,32,68,70,71,39,41,5,97,47,48,12,13,16,18,19,102,74,103,76,21,23,91,86,25,88,54],rl6:8,rl1:8,rl3:8,rl2:8,shown:[66,52,33,8,57,70,20,1,2,103,94,35,88,24,78,101,14,105,16,6
 ],accomplish:[23,101,30,74,43,87,25,16,17],space:[84,32,35,68,69,4,70,71,38,96,8,5,45,46,48,11,12,15,16,50,52,102,74,103,76,110,23,107,24,91,85,88,111,26,115],oldval:[45,39,70,2,47],rational:[37,84,70,102],ldrr:52,release_34:23,fiddl:[16,105,9],release_31:23,release_30:23,release_33:23,release_32:23,argu:68,argv:[66,8,20,103,98,80,83],ldrd:86,mandelconverg:[14,2],argc:[66,8,20,103,98,70],ocamlc:29,card:[73,34],care:[23,38,68,52,40,5,33,84,45,86,93,76,115,11,70,4,27,15,16,6,97],xor16rr:84,couldn:[32,40],adc32rr:6,gcmetadataprint:74,enginebuild:[71,39,45,2,47,48],unwis:[70,96],adc32ri:6,lambda:[68,16],blind:84,directli:[30,84,73,67,46,35,68,36,4,70,6,96,8,45,2,47,48,12,13,14,15,16,50,100,52,102,74,20,103,76,21,80,23,60,107,29,40,86,25,88,111,113],subrang:103,rint:70,yourself:[23,64,25,16,115],stringref:[39,20,91,103,68,16],size:[30,91,0,32,33,68,36,70,6,66,38,39,84,8,41,112,45,2,47,48,10,11,49,42,99,15,16,18,52,102,74,20,64,103,76,110,22,78,55,96,83,24,40,85,86,62,88,111,54,90,115],su
 b_ri:115,yypvr:105,silent:[25,70,115,40],caught:[107,68,70],yin:91,type_block:111,himitsu:23,checker:[21,102,61],cumul:84,friend:97,editor:[23,25,68,105,65],nummeta:74,ariti:74,especi:[30,25,52,32,20,97,68,34,103,86,3,49,59,4,16,50],dw_tag_interface_typ:103,apple_nam:103,cpu0:51,cpu1:91,qual:70,llvmtop:76,mostli:[23,38,39,60,52,30,32,20,84,86,47,35,59,11,13,24],quad:[70,52],than:[30,91,31,32,77,34,46,68,36,70,66,37,38,39,84,40,41,54,43,97,45,2,47,48,10,11,49,73,12,13,14,15,16,17,18,19,52,102,74,90,20,64,103,76,113,21,78,56,58,96,23,60,83,24,61,85,86,25,88,50,111,107,26,65,27,105,28,29,115],image_sym_type_word:108,"0x432ff973cafa8000":70,d02:55,xcore:[23,84,104,87],spisd:52,browser:[37,82],loweratom:30,anywher:[105,5,45,10,90,54,32,65,15,70,6,18],getint32ti:68,cc_sparc32:52,bitcast:[30,52,40,74,32,102,55,5,78,70],caus:[30,61,0,84,1,5,94,68,36,4,70,71,64,39,96,8,112,44,45,2,47,10,15,16,97,18,74,20,75,55,76,78,80,23,83,29,40,86,91,63,25,50,54,65,24],feat_segstacks_x86:84,libcal:[30,33]
 ,fldcw:84,mccodeemitt:[84,21],begin:[84,32,93,35,68,4,70,71,39,96,40,101,44,45,47,12,13,14,15,16,18,19,52,74,20,103,23,59,29,91,87,25,88,111,28],importantli:[13,68,47,40],numrecord:88,toplevel:[12,13,14,15,18,19],setdebugloc:39,cstdlib:54,getpointers:74,renam:[23,68,31,16,45,103,41,65,15,70],cmpoper:32,"_p1":103,"_p3":103,callinst:16,llvm_libdir_suffix:60,add_reassoci:[12,13,14,15],concurr:[37,60,74,16,29,86,70],image_file_bytes_reversed_lo:108,fifth:[66,70,52,8],onli:[72,30,91,0,32,33,1,68,110,46,35,3,36,69,4,54,70,6,97,66,37,38,39,84,8,41,5,43,44,9,2,47,48,10,11,49,45,12,13,14,15,16,17,18,19,102,101,52,53,74,90,20,75,64,103,76,77,22,78,79,80,57,93,96,23,59,60,73,83,24,40,86,25,88,50,111,107,26,65,114,28,29,115],ratio:58,image_rel_i386_dir32nb:22,expr_prec:[12,13,14,15,18,19],endloop:[39,15,45,2,47],overwritten:[88,84,70],llvminitializesparctargetinfo:52,cannot:[30,68,0,94,35,4,5,71,38,40,70,46,11,83,52,102,74,20,76,110,22,78,16,29,84,86,109,25,112],foo4:[63,90],targetjitinfo:[84,5
 2],mrm6r:52,addmoduleflag:39,operandlist:115,seldom:32,intermitt:23,bio_new:24,object_addr:74,type_code_ppc_fp128:111,gettypenam:16,rrinst:115,"0x0000000000d953b3":98,sometest:33,copycost:52,istreambuf_iter:8,"0x48c978":24,foo_test:10,concern:[102,74,16,25,26,70],"1svn":93,brace:[68,5,10,70,16,115],dityp:39,mrminitreg:52,printinstruct:[21,52],regcomp:24,between:[30,91,31,32,33,93,68,69,4,70,97,71,37,64,8,5,43,44,77,46,47,48,73,12,13,84,16,17,66,52,102,74,20,103,76,21,78,23,59,82,90,29,40,86,109,25,88,111,65,27,28,24,115],x86reloc:52,modulelevelpass:76,paramet:[30,84,32,1,68,3,70,6,71,8,41,73,16,19,52,102,74,20,103,76,21,56,60,107,24,91,111,29],constantpoolsect:52,clang_cpp:10,typedef:[68,91,16],"__text":84,intregssubclass:52,dw_tag_subrange_typ:103,mono:29,pertain:[65,25,103,107],inputfilenam:20,nearbi:32,inconsist:[68,103,102],doesnotaccessmemori:40,qualtyp:68,image_sym_type_struct:108,gr32:[84,6,115],overview:[68,31,73,33,35,69,70,71,37,104,8,47,10,13,50,66,74,20,76,23,107,40,87,6
 2,88,111,26,105],my86flag:91,exploit:[41,20],clarif:[104,25,68],invert:10,shim:30,valuekind:68,invers:30,uglifi:[12,48],getentryblock:[45,39,16],kdevelop3:23,derefer:[70,16,103,102],normalformat:20,"_global__i_a":97,rubi:74,getjitinfo:[84,52],x86_fastcal:84,thischar:[39,41,54,43,45,2,47,48],eip:6,module_code_vers:111,global_context:[12,13,14,15,19],retcc_x86_32_c:52,fastemit:21,fneg:70,initializenativetargetasmpars:[39,45,2,47,48],dw_at_artifici:103,stdout:[23,108,35,12,13,14,15,70,18,19],metric:[76,24,58,93],henc:[23,28,20,97,87,88,90],worri:[23,39,82,54,20,70,18],onlyreadsmemori:40,eras:[39,41,20,97,45,2,47,103,86,65,16],bigblock:80,antisymmetri:32,develop:[84,73,33,34,67,93,68,4,6,37,104,97,45,10,49,15,50,51,102,74,20,103,76,113,23,60,107,29,61,87,62,25,26,65,90],proto:[39,41,54,45,2,47,48,12,13,14,15,18,19],"__nv_powf":8,sizeofimm:52,image_scn_lnk_info:108,cc1:98,epoch:[91,96],cindex:52,externalstorag:20,document:[30,61,91,31,32,33,34,67,93,35,68,69,4,70,6,71,37,64,39,104,101,8,
 41,9,48,10,49,73,12,84,16,66,52,102,74,20,103,76,113,21,22,78,58,23,81,59,60,90,29,40,86,87,62,25,88,111,107,26,65,105,28,115],finish:[0,31,32,93,48,70,71,39,41,45,2,47,98,12,13,14,15,83,18,19,76,107,84,105],closest:[39,70],ssub:70,preassign:84,someon:[38,68,84,64,25,11,105],removebranch:52,freeli:[25,86],tradition:[84,40],"__cxa_allocate_except":107,pervas:[16,101],whose:[66,28,68,52,40,110,16,84,45,2,103,25,83,111,54,14,15,70,18,115],createstor:[39,45],destreg:84,bodi:[30,68,32,70,6,39,41,5,45,2,47,48,12,13,14,15,16,18,19,52,20,103,76,83,29,85,111,54,28,24,115],ccc:[70,9,111],neon:[37,84,9,34,21,78],noaa:30,touch:[30,68,16,103,76,70],tool_verbos:[23,87,65],speed:[68,20,45,10,25,15,24],create_modul:[12,13,14,15,19],death:24,struct:[38,39,111,52,0,74,5,20,91,45,46,103,76,68,11,49,70,102,15,16,29],bb0_29:8,bb0_28:8,getx86regnum:52,bb0_26:8,filecheck:[10,112,57,5,67],desktop:62,identif:[70,9,28,23],gettoknam:39,treatment:[74,52],versa:[10,16,86],earli:[68,52,8,45,65,15],imul16rmi8:84,
 "0x82638293":103,read:[30,61,0,32,94,35,68,36,98,70,6,97,37,7,39,95,84,8,41,5,43,44,45,2,47,48,10,11,104,73,12,14,15,16,17,19,52,74,90,20,75,38,103,77,78,79,80,57,96,92,23,105,82,109,83,29,40,86,87,91,25,88,54,111,64,65,114,28,24],cayman:104,amd:[72,21,9,104],regfre:24,googletest:1,amp:104,bangoper:28,funcresolv:16,benefit:[30,68,40,74,24,102,103,16,29,50],lex_numb:[12,13,14,15,17,18,19],output:[30,61,91,31,84,33,1,94,35,68,36,69,70,6,37,7,39,95,96,8,5,44,45,2,47,48,10,42,92,12,13,14,15,16,18,52,74,54,20,75,64,103,76,21,79,80,57,110,58,23,105,60,106,83,24,40,108,87,109,77,112,65,27,114],debug_pubtyp:103,matur:[74,20],initid:111,cmake_install_prefix:[60,35,9],viral:25,globalvalu:16,libstdc:[23,68,9],debug_with_typ:16,extralib:65,blockidx:8,lto_codegen_set_debug_model:90,v2i32:70,n64:29,tdm:113,tok_binari:[39,45,2],sixth:52,objectbufferstream:71,asan:[24,29],flagprototyp:39,"throw":[30,107,84,46,76,49,4,70],dw_tag_subprogram:103,src:[100,52,31,33,84,93,70,50],sra:[28,115],central:[4,1
 03,107],greatli:[73,29,103],underwai:29,image_sym_class_sect:108,srl:[28,115],numbit:16,chop:103,degre:[113,86,49,0],dw_tag_subroutine_typ:103,backup:63,processor:[23,60,52,0,74,104,20,84,103,87,21,29,78,80,65,70,6],valuecol:69,bodylist:28,op3val:52,llibnam:20,unregist:76,xxxbegin:16,outloop:[39,15,45,2,47],yout:91,your:[61,91,31,45,33,34,94,35,68,101,70,6,66,37,38,39,84,8,41,5,43,97,9,2,47,48,10,11,49,12,13,14,15,16,17,50,52,102,74,20,64,76,96,23,81,59,60,82,83,24,40,86,87,62,63,25,113,65,105],parsebinoprh:[39,41,54,45,2,47,48],verifyfunct:[39,41,45,2,47,48],loc:[89,39,103,52],log:[30,0,32,33,1,40,83,70,16],opengl:[38,68,11],aren:[23,38,84,102,30,74,70,40,68,47,48,35,25,11,12,16],haskel:[16,38,11,70],start:[72,30,91,0,31,32,33,1,93,94,35,68,98,70,66,37,38,39,84,8,41,112,43,97,9,2,47,48,10,11,49,45,12,13,14,15,16,17,18,19,52,102,74,20,64,103,76,113,96,23,60,82,73,83,24,40,87,25,111,54,26,65,105,115],low:[68,32,36,4,70,37,64,8,54,45,2,14,15,16,18,52,102,74,20,103,57,84,111,115],lot:[
 30,84,33,34,68,70,6,38,39,101,41,54,43,97,45,2,48,11,12,14,15,16,17,18,19,52,102,74,20,64,103,76,56,23,83,29,91,62,25,65],colder:58,submiss:25,branchinst:3,satur:[14,2],addresssanit:[24,70,29],furthermor:[70,102,5,30],"default":[30,91,0,45,33,1,68,46,94,35,3,101,70,6,71,7,39,96,8,41,5,97,9,2,47,48,10,49,92,12,13,14,84,16,50,19,66,100,52,74,54,20,64,76,21,22,89,79,80,110,23,60,24,40,87,62,77,88,111,112,65,27,114,29,115],tok_def:[39,41,54,43,45,2,47,48],start_bb:[13,14,15],bucket:[16,103],v32:8,loadabl:[76,65],scanner:[43,17],f6d55d:66,opnam:52,producess:[23,87],value_1:26,value_2:26,valid:[30,31,32,93,70,71,37,39,8,41,5,97,45,2,47,48,10,73,12,13,14,15,16,18,19,100,102,20,103,55,76,77,80,58,60,29,91,25,88,54,28,24],release_19:23,release_18:23,release_17:23,ignor:[0,32,36,70,37,39,40,41,5,43,44,45,2,47,48,12,13,14,15,16,17,18,19,52,20,103,58,23,84,25,111,54,26,65,27],you:[30,61,91,31,32,33,1,34,67,93,94,35,68,101,4,98,70,6,66,37,38,39,84,8,41,5,43,97,9,2,47,48,10,11,49,45,12,13,14,15,1
 6,17,18,19,52,102,74,54,20,75,64,103,76,21,56,79,80,115,96,92,23,60,82,73,83,24,40,86,87,62,63,25,50,111,112,113,65,105,28,29,99],release_14:23,release_13:23,release_12:23,release_11:23,poor:[13,68,47],polar:91,registri:[74,76],base_offset:73,cmake_minimum_requir:60,binfmt:23,resulttyp:70,pool:[52,84,76,88,111,36],namedvalu:[39,41,45,2,47,48],bulk:[45,15,16,84],ipsccp:30,adc64mr:6,value_n:26,skeleton:23,osx:96,messi:84,ssl3_read_byt:24,month:[37,93],correl:[74,70],"__cxa_end_catch":107,getglob:52,pandaboard:34,paramidx:111,mrmsrcmem:52,getnullvalu:[45,39,16,2,47],"_ri":115,cpufrequtil:34,sparcinstrinfo:52,articl:[30,23,32,45,47,13,15],sdisel:59,gcfunctionmetadata:[74,88],phielimin:84,"_rr":115,datalayout:[39,52,8,74,84,45,2,47,48,55,49,111,12,13,14,15,70],verb:[65,68],mechan:[68,0,73,33,4,70,71,37,8,41,16,19,74,103,55,76,107,29,84,63,111,26,65,28],veri:[30,84,0,32,33,34,93,68,70,6,97,37,38,40,41,5,43,44,45,2,47,48,10,11,49,99,12,13,14,15,16,17,18,19,102,74,54,20,103,76,21,23,83,24,9
 1,86,25,111,107,27,115],passmanagerbas:52,targetregisterdesc:[84,52],methodbodi:52,eatomtypetag:103,emul:[64,84,70,68],managedstat:16,cosin:[70,52],customari:[20,70],dimens:70,fixedt:103,preserveal:70,casual:[65,25],heartble:24,kistanova:113,dofin:[76,52],nand:70,fpformat:[6,115],isobjcclass:103,llvmlibspath:65,consecut:[28,0,5,103,55,76,78,70],"0x00000100":103,signextimm:84,modular:[26,76,75,68,40],minor:[38,68,32,84,93,62,25,11],exeext:[10,65],mclabel:84,strong:[5,97,86,25,32,70],modifi:[30,84,73,33,35,68,69,70,64,96,8,101,97,45,15,16,52,74,20,103,76,23,83,40,86,25,26,65,27],trunc:[70,0],divisor:70,ahead:[23,38,39,54,43,61,68,76,35,25,11,17,18],dform_1:84,t1_lib:24,amount:[30,61,32,68,70,6,64,43,97,48,12,83,17,74,20,75,76,77,80,16,84,85,21,88,107,65],lto_module_create_from_memori:90,module_code_datalayout:111,sphinx_warnings_as_error:60,initializealiasanalysi:40,ask:[31,73,93,35,37,38,39,40,54,97,45,47,11,32,13,15,16,18,99,64,103,76,23,87,25,65,28,115],href:84,famili:[38,70,103,35
 ,11,73,72,16],sequencetrait:91,dangl:[13,16],"0x710":79,is64bitmod:52,isimmedi:52,zorg:113,massag:68,formul:4,bash:[4,105],libxml2:9,taken:[30,38,84,96,52,40,31,70,20,65,107,3,11,49,32,4,16,6],distfil:65,zork:115,vec:[70,16],build_arch:[65,50],cbtw:84,valuetyp:[84,6,52],statepoint:73,regoffset:27,oblivi:78,x01:108,targetcallingconv:52,"0b000111":52,x00:108,x86instrmmx:52,histori:[23,25,82],ninf:70,indirectbr:70,reindent:68,addrspacecast:70,templat:[30,68,32,4,70,6,37,52,40,41,16,101,74,20,103,76,21,23,29,91,87,105,28,115],vectortyp:16,unreli:[24,40],parsabl:73,phrase:68,mabical:29,anoth:[30,91,32,34,46,35,68,69,4,70,6,66,38,39,84,8,41,5,97,9,2,47,48,10,11,45,12,13,14,15,16,18,52,74,20,75,64,103,76,22,78,96,59,73,29,40,86,25,88,111,54,26,65,105,90,24,115],llvm_enable_rtti:60,snippet:[74,16],reject:[38,39,41,70,20,97,45,2,47,48,11,93,12,13,14,15,5,19],getarg:39,rude:107,personlist:91,secondlastopc:52,unlink:[41,16],retcc_x86common:52,"0x00003500":103,lifetim:[74,16,84,103,46,76,49,70]
 ,machinepassregistri:76,feat_asmpars:84,polit:84,help:[91,31,32,33,1,34,67,94,68,36,4,109,70,6,37,7,39,95,40,5,43,97,10,11,49,92,16,17,50,100,115,53,74,20,75,38,103,76,113,77,78,56,80,57,110,23,60,82,106,112,24,61,86,83,25,64,26,65,27,114,90,89],mbbi:84,soon:[31,54,47,76,25,13,90,18],mrmdestreg:[6,52],held:[25,70,82,78],ffi:97,hierarchi:[23,64,61,101,37,41,1,87,76,16],ffc:84,foo1:[63,90],foo2:[63,90],foo3:[63,90],dfpreg:52,overhead:[74,24,97,48,69,12,16],"0x7ffff7ed404c":98,complex:[30,68,0,32,93,4,70,6,38,39,54,45,2,48,11,99,12,14,15,16,18,52,74,64,103,76,24,84],segfault:29,eatomtypecuoffset:103,tok_els:[39,45,2,47],mergebb:[39,45,2,47],systemz:[23,84,104,87],finer:40,cee:16,dexonsmith:103,sentenc:68,wideaddr:70,ninja:[24,9],gmon:65,libllvm:62,stopper:31,addenda:104,x0c:108,iff:70,scalarevolut:[30,102,40],fulli:[23,38,68,102,0,54,29,84,45,2,103,58,11,111,30,80,14,15,70,6,18],heavi:[65,16],succ_iter:16,llvm_build_tool:60,longjmp:[70,38,11,107],beyond:[105,102,16,107,27,114,70,6],tod
 o:[30,64,82,31,73,24,84,9,103,76,21,99],ific:20,isunaryop:[39,45,2],ppcinstrinfo:64,safeti:[70,38,11,29,49],publish:[31,68,16],debuglevel:20,dynamci:70,astnod:21,regexec:24,unreview:25,labf:20,ast:[51,38,39,41,54,43,45,2,47,48,21,11,59,12,13,14,15,17,18,19],errorp:[39,41,54,45,2,47,48],dw_tag_volatile_typ:103,mystruct:102,pub:103,mips64:[23,29,87],reason:[68,32,4,70,64,39,40,41,54,43,9,47,48,10,49,45,12,13,15,16,17,18,19,101,102,20,103,76,21,23,73,107,24,84,85,86,25,26,105,115],base:[30,61,0,31,32,33,1,77,34,46,94,3,36,69,4,68,70,6,71,37,39,84,8,41,54,97,9,2,47,48,10,45,12,13,14,15,16,18,19,66,102,52,53,74,101,20,103,76,21,22,57,93,96,23,59,60,73,83,29,40,87,91,25,50,111,107,28,115],put:[30,84,73,93,68,70,66,38,39,40,5,43,45,47,98,10,11,32,13,15,16,17,74,20,103,76,83,91,86,105],asi:52,intermodular:[37,90],wglobal:68,asm:[8,107,84,77,111,80,114,70],basi:[43,74,16,20,2,36,14,70,17],bring:[38,68,74,73,11,16],launch:8,bitconvert:78,clangattrparsedattrkind:21,warpsiz:8,undergo:[30,70],as
 sign:[30,91,32,68,3,69,70,39,8,41,43,97,45,15,16,17,19,52,102,20,58,59,84,86,25,111,28,115],obviou:[30,38,25,40,32,103,84,83,2,48,21,11,68,78,86,12,88,14,70,97,54],ultrasparc3:52,islazi:52,isregist:84,uninterest:[43,17],module_block:111,implementor:[12,13,6,47,48],miss:[45,0,70,29,9,2,83,63,68,54,14,15,16,33,18],st6:6,st4:6,st5:6,nodetail:36,st7:6,st0:[6,52,115],st1:[84,78,6,52],st2:6,st3:6,scheme:[68,52,74,36,45,56,15,16],schema:[91,1,108,53],adher:[4,25,16,6,99],xxxgencodeemitt:52,getter:[21,16,103],bidirect:16,newabbrevlen:111,numroot:74,intrinsicinst:74,std:[68,0,32,101,64,39,96,8,41,54,43,97,45,2,47,48,16,52,20,75,107,29,91,24],grep:[23,60,20,84,34,10,5,33],stl:[23,68,30,24,91,16,97],sparsebitvector:16,rootmetadata:74,store:[30,84,32,33,5,71,39,96,8,70,43,97,45,46,49,73,15,16,17,50,66,52,102,74,20,103,78,56,79,58,23,59,60,107,29,40,85,86,88,18,111,54],str:[66,39,8,41,16,24,45,2,47,48,108,78,54,70],consumpt:[76,24,84],aliaseeti:70,toward:[70,25,16,58,37],grei:31,randomli:42,tail
 callelim:30,gofmt:68,"null":[30,68,91,73,70,39,8,54,47,49,32,13,16,52,102,74,103,76,77,80,107,29,40,88],dllvm_target_arch:9,attrimpl:21,imagin:32,unintend:30,bz2:23,lib:[32,35,36,4,98,37,64,39,41,45,2,47,48,16,50,100,52,74,20,103,76,21,57,23,60,29,84,87,63,65,24],lic:30,ourfunctionpass:16,lit:[60,1,67,10,35,65,50],"__apple_objc":103,useless:[38,103,47,11,78,13],numfunct:88,clangdeclnod:21,mixtur:115,setjmp:[70,38,11,107],c_ctor_bas:5,maco:[23,97,16],alpha:[70,52],filenameindex0:66,isbarri:[6,115],hipe:[84,70],clear:[68,46,70,39,41,54,45,2,47,48,12,13,14,15,16,18,19,102,74,75,25,26,65],implicitdef:84,clean:[30,84,23,112,61,87,93,76,8,65,90,97],latest:[31,29,5],test1:[10,105],clangattrparsedattrlist:21,stackprotectorcheck:70,v16:8,instrins:70,i32imm:[52,115],"3x4":70,get_instrinfo_named_op:52,test5:5,ptrval:70,coerc:32,delin:1,pretti:[30,32,33,4,41,54,43,45,2,47,48,12,13,14,15,17,18,19,102,76,56,24,27,105,28,115],setnam:[39,41,45,2,47,48,16],less:[30,68,31,32,1,34,46,70,6,66,38,39,96,
 40,41,54,43,97,45,2,47,48,10,11,12,13,14,15,16,17,18,19,74,20,103,78,23,24,84,111,105],lastopc:52,adc32ri8:6,createfsub:[39,41,45,2,47,48],suspect:75,darwin:[39,84,10,88,79,65,70],ymm:70,defaultdest:70,prolang:33,parenexpr:[39,41,54,45,2,47,48,12,13,14,15,18,19],has_asmpars:26,nativ:[91,45,33,35,70,38,39,84,8,41,112,97,9,2,47,48,11,12,13,14,15,16,19,100,52,102,64,103,77,96,23,60,83,29,61,86,63,88,111,26,65,90],same_cont:22,"133700e":[41,19],externalfnconst:30,setdata:68,rejit:[12,48],memmov:70,llvmlibdir:65,setpreservescfg:76,kawahito:84,"__llvm_profile_name_bar":66,ctaid:8,xword:52,close:[30,59,82,102,23,31,16,53,41,68,37,54,84,70,18,19],"0x0b17c0de":111,smallvectorhead:16,deriv:[30,68,73,69,70,6,71,64,96,43,16,17,101,74,103,55,76,59,84,25,26,65,28,115],glue:[84,97],libcmt:35,particip:[10,70,25,16,65],parse_unari:[14,15],pifft:33,won:[39,102,40,31,33,84,9,103,48,10,41,25,56,12,65,68,105,70],isprefix:20,cst_code_integ:111,honour:29,emitint32:74,end_block:111,makeup:16,fpform:6,numer
 :[35,70,6,39,41,54,43,45,2,47,48,49,99,12,13,14,15,16,17,18,19,52,20,110,29,28],isol:[68,83,84,45,10,15,16,58,115],lowercas:[12,52,48],numel:70,distinguish:[66,38,74,16,11,78,4,70],both:[30,84,0,32,1,93,94,68,101,70,6,71,38,39,96,40,41,5,97,9,47,48,10,11,45,12,13,15,16,18,19,66,52,102,74,54,20,103,76,21,23,60,73,83,24,91,85,86,87,62,25,88,111,107,26,65,28,29,115],clang_attr_identifier_arg_list:21,delimit:[28,27,70,72],fancyaa:76,lako:68,inalloca:[70,46],debug_typ:16,sty:6,getnumvirtreg:84,protector:[70,103],block_par:[13,14,15],"__objc":70,jeff:4,byval:[84,70,111],header:[30,68,9,33,35,4,70,71,37,39,96,101,97,45,2,47,49,13,14,15,16,50,66,100,52,20,103,21,79,57,23,60,108,86,87,88,111,26,65],instrsch:16,"100mb":65,linux:[23,68,60,98,37,104,29,84,9,34,48,10,63,65,93,97],bridg:29,forgiv:32,llvm_enable_thread:60,stamp:96,territori:23,empti:[68,32,1,70,39,41,54,45,2,47,48,10,73,13,16,18,19,52,74,20,103,79,60,107,24,91,65,28,115],destructor:[68,16,97,76,107,70],newcom:[15,45,6,99],sslverif
 i:23,newinst:16,as_float:[12,13,14,15],box:[84,103,82],lattner:[38,11],imag:[71,29,84,2,110,22,14,70],ada:107,imac:0,coordin:[73,91],modrefv:115,imap:23,look:[30,91,32,1,93,35,68,101,98,70,66,37,38,39,84,8,41,5,45,2,47,48,10,11,12,13,14,15,16,18,19,52,102,74,20,64,103,76,21,79,23,60,90,24,40,85,86,87,63,25,88,50,111,54,26,105,28,29,115],fptosi:70,ramif:102,"while":[30,68,0,31,32,1,46,69,4,98,70,6,37,38,39,40,41,5,43,45,2,47,48,10,11,99,13,15,16,17,18,102,20,75,103,76,23,59,60,82,83,24,84,62,88,111,54,65,90,115],dw_lang_c_plus_plu:103,loos:[65,6],loop:[30,68,0,32,70,38,39,40,41,54,43,45,2,47,48,11,49,12,13,14,15,16,17,18,19,52,74,76,58,23,59,24,84,86,115],pack:[31,84,103,41,49,111,70,19],malloc:[74,16,38,11,76],pragmat:29,readi:[32,93,71,39,41,54,43,45,2,47,48,12,13,14,15,17,18,19,20,103,76,29,63,25],readm:[10,23,25,105],"__gcmap_":74,thesparctarget:52,hideaki:84,"0x00001203":103,quadrat:[84,77,16],targetlow:[64,84,83,52],fedora:23,grant:[32,25],tokinteg:28,belong:[70,20,16,32],llvm_
 site_config:35,indvar:[76,70,16,30],octal:[20,96,115],curloc:39,conflict:[23,39,115,41,70,84,45,2,47,48,10,25,12,13,14,15,16,6,19],"0b10":115,goodwil:25,ccif:52,optim:[30,61,0,32,33,34,67,46,94,35,68,69,70,66,37,38,39,84,8,41,5,43,97,45,2,47,48,10,11,49,73,12,13,14,15,16,17,50,19,51,52,102,74,101,20,75,64,103,76,113,77,78,80,55,23,59,83,24,40,86,87,62,63,88,111,112,26,65,90,29],image_sym_class_type_definit:108,va_copi:70,temporari:[30,59,91,16,33,1,10,68,65,84,70,97],user:[72,30,91,0,32,33,1,77,93,68,36,70,6,66,37,38,39,84,8,41,112,43,45,2,47,48,10,11,12,13,14,15,16,17,18,19,51,52,74,20,103,76,21,58,96,23,59,60,82,83,24,40,86,105,62,25,54,113,65,27,114,90,29,115],function_block:111,"3gb":35,vreg:84,numarg:[39,88],"0x16677e0":98,older:[23,52,20,34,25,65,27],mctargetstream:84,pointtoconstantmemori:40,reclaim:[59,70],use_:16,positionaleatsarg:20,basiccg:30,weakest:[84,86],predetermin:40,cout:[91,68,97,8],isunord:86,accumulateconstantoffset:32,afre:46,elect:25,dw_ate_unsigned_char:103,u
 ndeclar:[41,19],password:[113,25],recurs:[30,38,41,70,43,1,45,2,47,74,21,11,54,65,13,14,15,16,17,18,19],shortcut:[43,17,18],supersparc:52,codegener:61,gnueabihf:[9,34],march:[23,61,103,77,80,5],arm_aapcscc:111,mcsectionelf:84,xterm:68,game:25,optimizationlist:20,characterist:[64,52,16,84,108,70],isproto:111,pcmarker:70,outright:102,success:[91,68,70,39,41,54,45,2,47,48,12,13,14,15,18,19,52,53,76,23,61,25],signal:[20,86,98,10,70,24],resolv:[71,84,41,70,29,1,47,48,76,25,90,65,12,13,16,6,19],"______________________________________":16,popular:[23,84,34,40],regionsforfile1:66,regionsforfile0:66,ptroff:84,some:[30,91,0,31,32,33,1,77,34,46,94,35,3,69,4,68,70,6,110,37,38,39,84,40,41,5,43,97,9,2,47,48,10,11,49,45,12,13,14,15,16,17,18,19,52,101,74,90,20,99,64,103,76,21,78,56,102,93,96,23,59,60,82,73,83,24,61,85,86,87,62,25,88,111,54,26,65,105,28,29,115],urgent:25,mnemonicalia:84,getfunctionlist:16,mem_address:84,uselistorder_bb:70,addpreserv:[76,40],printinlineasm:52,pathsep:10,n2930:68,slas
 h:[103,96],castinst:16,bcanalyz:[111,67,36],cgi:24,run:[30,61,107,0,31,32,33,1,34,93,94,35,68,98,70,6,71,37,38,39,84,8,41,5,43,97,9,2,47,48,10,11,49,45,12,13,14,15,16,17,18,19,66,100,52,74,54,20,75,103,76,113,21,78,23,60,73,83,24,40,86,87,62,63,25,88,50,112,26,65,90,115],stem:16,step:[30,91,31,45,33,93,35,69,70,64,39,84,8,101,9,2,47,32,13,14,15,16,51,52,102,76,21,23,60,83,24,40,87,107,113,90,29],ditypearrai:39,movsx64rr8:84,curtok:[39,41,54,45,2,47,48],assignvirt2phi:84,subtract:[66,24,70,64],"_ztid":70,blocksizei:8,idx:[39,102,41,45,2,47,48,68,70],nnnnnn:84,shini:76,blocksizez:8,f31:52,blocksizex:8,block:[30,84,0,31,32,68,46,94,3,36,70,37,39,8,41,5,44,45,2,47,48,49,12,13,14,15,16,18,19,52,53,74,103,76,21,80,58,59,107,40,85,25,88,111,54,105,115],nvvm:8,use_llvm:[12,13,14,15,19],gcroot:[74,88,70],aq2:70,within:[30,91,32,33,1,68,70,39,84,8,5,97,45,2,47,48,73,12,13,14,15,16,50,101,102,74,75,103,55,78,23,59,83,40,88,111,107,65,115],loadsdnod:16,proj_install_root:50,ensur:[30,84,0,73,93,
 68,36,70,39,8,41,5,97,45,2,10,15,16,19,100,52,20,75,76,22,23,107,40,86,87,25,88,111,65],llvm_package_vers:60,mach:[79,104,70,103,111],properli:[37,68,40,83,20,84,45,86,48,10,22,26,15,70,33],loopunswith:49,pwd:[23,24,9],bio_s_mem:24,vfprintf:70,newer:[23,35,25,98],cmpxchg:[70,86],flagsfeatureb:91,flagsfeaturec:91,flagsfeaturea:91,specialti:16,info:[30,84,0,33,1,98,70,38,39,43,45,2,47,48,11,12,13,14,15,16,17,52,74,103,76,21,79,23,60,107,91,111,114,90,115],fde:84,"0xc3":115,i65:70,clangattrpchread:21,similar:[30,84,0,32,34,68,4,70,39,96,8,41,5,43,2,47,48,10,12,13,14,16,17,50,19,100,52,102,74,20,76,21,22,23,107,24,91,86,25,111,115],createdefaultmypass:76,obviat:50,reflectparam:8,doesn:[30,84,1,68,93,3,4,70,66,38,39,96,40,41,5,43,97,45,2,47,48,10,11,99,12,13,14,15,16,17,18,19,101,102,74,54,20,76,78,83,29,61,86,63,25,88,107,24,115],repres:[30,84,73,1,68,3,70,6,66,64,39,96,8,41,54,97,45,2,47,48,49,12,13,14,15,16,18,19,52,102,20,103,21,78,56,58,107,29,40,86,111,28,115],arg_iter:[39,41,45,2,
 47,48,16],incomplet:68,nextvari:[2,47],minsiz:70,titl:[25,82],speccpu2006:33,nan:[80,77,70,103],accross:70,setenv:65,"0x00007fff":84,dosometh:68,resign:25,xtemp:86,drag:82,eval:[30,40],parseenvironmentopt:20,canfoldasload:6,svn:[23,60,82,0,24,62,93,10,35,25,88,33,19],typeid:[32,64,111,107],codeblock:[74,23],infrequ:76,addmbb:84,orbit:[14,2],devminor:8,depth:[30,32,20,84,103,47,63,13,6],loadobject:71,unconnect:102,intervalmap:16,msbuild:[35,60],getkind:[21,101],image_scn_mem_preload:108,compact:[38,39,74,84,11,36,88,16],friendli:[37,68,54,25,99,27,18],"__llvm_profile_name_foo":66,unsimm:84,breakcriticaledg:76,aris:[70,25,16,102],instr_iter:84,yoyodyn:25,then_bb:[13,14,15],roots_siz:74,runnabl:[23,87],nonatom:103,llvmdisasminstruct:27,weakvh:16,llvm_enable_doxygen:60,use_llvm_target:[12,13,14,15],dw_tag_const_typ:103,ccifnest:52,initializer_list:68,lazier:29,relink:[100,83],calleef:[39,41,45,2,47,48],jump:[30,39,52,20,61,47,22,111,65,13,84,70,50],imper:[68,74,45,47,13,15],download:[23
 ,60,52,31,29,9,93,10,63,113,65,16],click:[35,82],hasoneus:68,poke:111,image_scn_lnk_nreloc_ovfl:108,espresso:33,cell:52,experiment:[37,64,73,29,88,70],registerschedul:76,ramsei:84,init_v:15,legalizeact:52,becom:[30,68,0,34,70,6,101,54,45,47,10,49,13,15,16,18,52,102,20,76,78,29,84,88,65],accessor:[76,54,84,103],"_source_dir":60,startexpr:[39,15,45,2,47],convert:[30,84,32,1,67,70,64,39,8,41,43,45,2,47,48,11,49,92,12,13,14,15,16,17,19,52,102,20,38,76,21,78,56,79,23,91,108,86,87,28,115],copyright:[76,25,97],vbr:[96,111,36],solaris2:76,findings_dir:24,chang:[30,91,31,32,33,1,68,46,35,3,101,70,71,37,64,39,95,84,8,41,5,44,45,2,47,48,49,73,12,13,14,15,16,97,19,100,52,53,74,20,103,76,113,78,56,102,93,23,81,59,60,82,83,29,40,86,87,62,25,88,111,112,26,65,90,24,115],hexagon:[23,21,84,87],epilogu:[74,29,70,52],chanc:[71,3,43,91,17,25,6],testcase_dir:24,selectinst:68,n3272:68,although:[68,1,35,70,64,2,10,16,19,101,53,74,20,76,23,29,84,86,111,26,65,105],danger:[16,5,70],revok:25,win:[68,16,40],deg
 en:70,dyn_cast:[37,68,101,52,74,21,16],"boolean":[30,68,60,52,20,84,47,77,111,26,13,70,115],makefileconfigin:65,externallyiniti:70,getrawsubclassoptionaldata:32,implic:[84,25],recordid:111,fibi:[15,45],remaind:[66,23,64,52,107,84,10,26,70],llvm_enable_warn:60,"0x00ff0000":84,numelt:111,benchmark:[23,0,31,33,103,10,25,16,50],landingpad:[30,70,107],debugloc:[29,39],nvptx:[23,104,37,84,87,8],findlead:16,retriev:[71,96,82,8,20,91,76,88,16],image_scn_gprel:108,perceiv:[38,11],memory_order_acq_rel:[70,86],linearscan:[76,80,84],meet:[76,23,25,84,32],control:[30,68,0,73,1,46,35,70,71,38,39,8,41,54,43,44,45,2,47,48,11,12,13,14,15,16,17,18,19,51,52,20,64,103,76,77,80,23,60,83,29,84,85,87,25,88,107,65,90],malform:[30,83],sudo:[23,34],llvm_use_intel_jitev:60,compactli:115,myfooflag:91,sought:70,emitepilogu:52,clang_attr_arg_context_list:21,egrep:23,narr:32,addpreemitpass:52,dissolv:65,tag_base_typ:103,templatearglist:28,lto_module_is_object_fil:90,live_s:74,eliminatecallframepseudoinstr:52,alia
 sanalysiscount:40,targetdata:30,"0x3feaed548f090ce":48,filterclass:69,zext:[70,49,56],vsetq_lane_s32:78,pseudolow:21,subtyp:[107,52],primaryexpr:[54,18],jne:84,onzero:70,distzip:65,outer:[39,91,45,46,47,76,68,13,15,70],consensu:25,pushfl:84,topdistdir:65,foreach:[68,28,6,115],dw_tag_auto_vari:103,label_branch_weight:3,handl:[30,84,0,73,46,4,70,37,38,39,101,8,41,54,43,45,2,47,48,11,13,14,15,16,17,18,19,52,74,20,103,76,22,78,56,80,60,90,29,91,86,25,88,107,26,28,115],auto:[37,39,53,0,84,103,68],handi:[41,65,105,16,19],memberlist:52,armgenregisterinfo:21,p15:8,p16:8,p17:8,front:[30,84,93,68,70,37,38,39,43,97,45,2,47,48,11,12,13,14,15,16,17,50,102,74,103,23,107,61,87],gridsizei:8,modr:84,somewher:[76,101,41,5,33,2,10,107,14,70,19],ourfpm:[39,45,2,47,48],mode:[31,1,93,5,6,37,39,96,45,15,16,100,52,20,78,23,60,106,24,84,87,25,111,65,29],basicblockpass:76,acquirereleas:86,unwind:[30,52,107,29,84,46,22,49,57,70],globl:[22,8],selectiondag:[30,64,52,84,86,21,16],grok:[41,97,19],chunk:[30,68,111
 ,41,84,85,103,78,19],special:[30,61,0,32,1,4,70,6,37,38,39,84,8,43,9,98,10,11,45,15,16,17,52,102,74,20,103,76,78,23,40,86,87,91,25,88,111,26,65,28,115],image_sym_type_byt:108,"0x00000130":103,image_scn_lnk_oth:108,influenc:[76,59,103,78],discharg:49,suitabl:[71,30,8,74,16,20,84,10,111,70,66],hardwar:[23,104,52,8,84,35,49,80,70],statist:[66,40,29,75,76,77,36,80,16,33,50],iostream:[39,68,97,8],spec95:33,lcssa:[30,59],"__cuda_ftz":8,manipul:[23,97,53,74,16,84,45,56,15,70],undo:78,parallel_dir:[65,50],ssl_set_accept_st:24,machineinstrbuild:84,ecx:[84,22,6,115],image_scn_mem_writ:108,bodyexpr:[39,15,45,2,47],bclinklib:65,membership:16,keep:[30,68,0,32,93,4,70,6,37,38,39,40,41,5,43,97,45,2,10,11,14,15,16,17,18,19,101,20,103,76,24,84,25,54,90],wrote:[64,39,70,102],dumpmymapdoc:91,svptr:70,linkallcodegencompon:76,qualiti:[76,84,34,93,10,25,70],fmul:[8,41,84,48,12,70,19],lshr:70,art:74,find_a:16,rs1:52,rs2:52,scalartrait:91,perfectli:[68,102,5,84,54,70,97,18],mkdir:[23,60,24,87,93,63,65],wra
 pper:[71,30,52,32,29,103,111,4,16],second_end:70,attach:[23,68,82,8,29,45,103,98,25,15,70],regionpass:76,functionpassctor:76,"final":[68,31,32,1,46,101,70,6,71,38,39,96,41,54,43,9,2,47,10,11,45,13,14,15,16,17,18,19,66,52,90,20,99,103,76,21,93,23,83,84,25,50,111,107,65,28,115],prone:[20,84,6,97,34],my_valu:68,rsi:6,deconstruct:84,methodolog:107,rst:[84,21,105],exactli:[30,68,73,1,4,70,40,5,48,32,12,16,101,74,20,103,76,22,78,24,91,111,26,115],rsp:[88,84,85,6],ehashfunctiondjb:103,bloat:68,a_ctor_bas:5,instvisitor:[64,16],openssl_add_all_algorithm:24,dubiou:96,bare:[70,100,16,52,88],f16:70,exhibit:[83,86],multhread:16,mergetwofunct:32,xor8rr:84,reg2:5,procnoitin:6,reg1:5,goldberg:74,lightli:[31,70],tabl:[30,84,0,32,33,67,93,36,69,70,6,71,37,38,39,96,40,41,54,45,2,47,48,11,73,12,13,14,15,16,18,19,51,52,53,101,20,103,21,78,79,57,23,107,29,91,110,111,65,90,115],need:[30,61,91,31,32,33,77,46,94,35,68,54,69,4,98,70,6,37,38,39,84,8,41,5,43,97,9,2,47,48,10,11,49,45,12,13,14,15,16,17,18,19,100
 ,101,52,53,74,90,20,75,64,103,76,21,78,56,80,57,93,58,96,23,102,105,60,73,83,24,40,85,86,87,63,25,88,50,111,107,26,65,27,114,28,29,115],altivec:84,border:84,fp5:[6,115],createfunctiontyp:39,"0x08":103,reloc_pcrel_word:52,"0x04":103,"0x05":88,"0x06":88,"0x07":88,"0x00":[66,88,96],parse_extern:[12,13,14,15,18,19],"0x02":[66,103],fileit:20,unawar:70,lgkcmt:72,platformstripopt:65,llvmgold:63,detector:[32,29],equal_rang:16,singl:[30,84,0,31,32,33,1,94,68,70,66,38,39,96,8,41,5,43,45,46,48,10,11,12,15,16,50,19,52,102,74,20,64,103,76,78,56,23,59,106,83,29,91,86,87,109,25,111,107,65,24,115],parseidentifierexpr:[39,41,54,45,2,47,48],discop:39,discov:[84,74,24,1,45,103,47,93,13,4,15],rigor:84,x86_ssecal:52,x86_fp80:[32,70,111],promoteop:64,url:[25,82,105],hasrex_wprefix:6,"0xe8":115,yaml2obj:108,indx:91,inde:24,llvm_parallel_link_job:60,unoptim:[23,77,87],"0x0d":88,"0x0e":88,constrain:[62,41,97,10,19,115],disable_assert:[62,23,93,87,65],"0x0a":[88,96],"0x0b":88,"0x0c":66,ssl_load_error_str:24,
 cute:[38,11],verbos:[23,1,96,106,91,87,65],objc:[37,105,103],molest:70,anywai:[30,68,9],varnam:[39,45,2,47,13,15],tire:[14,68,2,6],losslessli:32,envp:98,x86_thiscal:84,themodul:[39,41,45,2,47,48],add_to_library_group:26,gettyp:[68,16],tbb:52,coalesc:[80,44,16,84],shr:68,enabl:[84,0,92,1,34,68,70,6,66,7,95,112,97,98,10,16,52,74,20,75,103,76,77,78,80,23,60,106,24,91,85,87,62,63,25,65,27,90,29],getmbb:52,she:[113,6],contain:[30,61,0,31,32,33,1,68,34,93,94,35,3,69,98,70,6,71,37,39,95,96,8,41,5,9,47,48,10,49,73,12,13,54,84,16,18,19,66,52,102,74,101,20,103,55,76,113,21,22,78,79,110,58,23,59,60,109,90,24,40,87,91,63,25,88,50,111,107,26,65,114,28,29,115],shapekind:101,grab:[39,31,97,93,21,13,14,15,16],image_file_local_syms_strip:108,shl:[30,68,32,70,28,115],nolink:20,flip:68,vectorize_width:0,target_link_librari:60,image_scn_mem_16bit:108,mileston:[32,29],statu:[97,73,1,5,94,36,42,37,7,95,96,112,44,92,100,53,75,77,89,79,80,57,60,82,106,29,109,110,88,113,65,114,24],aros:29,correctli:[91,73,6
 8,70,54,97,47,10,32,13,16,50,102,20,103,76,60,107,84,85,86,25,18],writter:20,sectvalu:20,realign:70,state:[30,68,73,93,70,39,40,54,32,84,16,74,20,103,76,78,23,82,107,24,91,86,87,25,88,65,105],neither:[30,111,40,32,35,88,49,78,70],tent:70,vfp3:9,kei:[84,73,16,24,91,76,25,32,69,70,6],header_data_len:103,parseabl:73,setgraphcolor:16,eclips:23,thank:61,xxxreloc:52,admin:113,handledefinit:[39,41,54,45,2,47,48],dw_tag_inherit:103,test_format:1,unglamor:25,multi_v:20,orig:70,quit:[32,4,70,37,38,40,41,47,98,11,13,16,19,102,74,64,23,29,84,88,65,105],slowli:[23,25],addition:[23,84,30,74,16,20,40,86,63,25,26,65,70,29],classnam:114,libdir:[65,100],image_sym_dtype_nul:108,treat:[68,32,69,70,38,41,5,10,11,16,19,52,102,20,78,56,60,107,84,86,88,111,65,90],cputyp:111,alphacompilationcallback:52,otp:70,createcal:[39,41,45,2,47,48,16],acq_rel:[70,86],replic:[61,90,115,91],novel:[74,70,16],dw_tag_typedef:103,harder:[30,73,24,97,54,4,70,18],contextu:27,print_str:[12,13,14,15,18,19],engag:25,demo:[41,20,
 93,97,19],rootstackoffset:74,povray31:33,revis:[23,68,60,82,103,93,25,88,16],inf:[80,20,77,70,103],welcom:[32,35,38,39,104,41,54,43,45,2,47,48,11,49,12,13,14,15,17,18,19,76,23,25],parti:[73,25,68,50],mglibc:29,reloc_picrel_word:52,print_float:[12,13,14,15],sqrt:[91,70,0],ro_signed_pat:6,setcategori:20,matcher:[84,24,21,114],donoth:70,http:[23,39,82,51,31,37,24,9,93,10,41,35,25,113,68,33,19],tokprec:[39,41,54,45,2,47,48],effect:[30,68,73,33,34,4,70,40,2,47,10,49,13,14,16,52,102,74,20,103,76,80,60,29,84,111,65,27,28],isopt:20,llvm_use_oprofil:60,global_s:16,initi:[30,91,32,1,68,36,101,70,71,64,39,84,8,41,97,45,47,48,12,13,14,15,16,19,66,52,74,20,76,21,80,58,23,60,107,24,40,85,111,28,115],spreg:29,appendinglinkag:16,dllvm_enable_p:9,callgraphscc:76,isrematerializ:6,dw_form_strp:103,well:[30,84,0,32,93,68,98,70,6,64,39,8,41,112,43,97,45,2,48,10,49,73,12,14,15,16,17,18,19,20,75,103,76,23,82,83,29,40,86,63,25,111,54,26,90,115],makefileconfig:65,undefin:[30,61,60,52,8,16,29,0,68,86,115,21,
 90,78,102,110,70,6,97],sibl:[84,70],distanc:[70,91,16,102],memory_order_consum:86,mistaken:[12,48],aform_1:84,aform_2:84,namedvar:39,xs1:104,size1:70,size2:70,size3:70,outstream:74,dcmake_build_typ:24,densiti:[14,68,2],warrant:64,kick:[14,2],nodebuginfo:20,takelast:16,howto:[51,21,105],mcsectioncoff:84,add_gvn:[12,13,14,15],burden:[29,25,70],n2343:68,zchf:9,n2347:68,loss:[74,16],lost:[38,107,97,11,65,70],aliasresult:40,ldflag:[100,39,41,45,2,47,48,65],necessari:[84,73,93,68,4,70,71,64,39,96,40,5,97,9,98,10,49,16,66,52,74,20,76,78,56,58,23,59,60,107,61,86,25,88,65,105,90],rotl:64,lose:[76,38,11,103],profraw:66,page:[68,0,67,93,35,71,37,104,41,97,10,16,20,103,22,23,81,60,82,29,25,65],hasdelayslot:6,didn:[68,41,32,29,84,45,103,76,15,16,18,19],isnul:68,"04e":70,notfp:115,repeat:[30,31,32,103,83,107,27,70],vset_lan:78,home:[23,33,98,10,49,16],librari:[30,61,0,45,35,68,36,4,98,70,37,38,39,104,96,8,41,112,43,97,9,2,47,48,10,11,14,16,17,18,19,100,52,53,74,20,75,103,76,80,57,23,102,60,106,24
 ,40,87,91,62,25,50,111,54,26,65,114,90,29],hannob:24,win32:[10,4,35,84,23],setmcjitmemorymanag:[71,39,45,2,47,48],broad:[43,74,20,48,12,17],createexpress:39,overlap:[40,0,84,46,76,88,70],outgo:[70,58],asmstr:[6,52,115],myfunct:8,encourag:[30,38,68,23,61,25,11,16],ifequ:70,win64:29,usag:[30,68,0,32,70,6,66,37,96,8,112,43,46,10,73,16,17,20,103,76,21,60,83,24,84,63,88,26,65,29],prefetch:[104,70],nutshel:16,offset:[38,96,52,102,73,70,29,84,85,103,55,10,74,11,111,32,88,5,6,16],zeroormor:20,sk_squar:101,image_file_32bit_machin:108,testsuit:[65,5],bcreader:100,freedom:[70,16],viewvc:37,bodyitem:28,metadata_attach:111,cocoa:70,cmake_cxx_flag:60,attrtemplateinstanti:21,pointless:107,"0x00000110":103,gcov_prefix:94,image_file_removable_run_from_swap:108,"_cuda_ftz":8,downgrad:97,inner:[37,68,112,91,46,70,16],add_excut:60,interleave_count:0,feat_segstack:84,pty2:70,addpassestoemitfil:76,eax:[52,84,22,5,6,115],gain:[32,20,29],spuriou:[68,70],overflow:[24,70,49,102],highest:[39,41,54,45,2,47,48,
 78,12,13,14,15,70,18,19],eat:[39,43,41,54,20,45,2,47,48,12,13,14,15,17,18,19],liblto:[63,90],dmb:86,displac:84,displai:[66,30,84,52,33,43,57,20,1,68,103,109,113,94,25,36,101,27,110,17],sectiondata:108,asynchron:86,cruel:105,"0xffbef174":76,limit:[30,84,73,68,70,37,39,40,112,102,2,47,48,49,12,13,14,16,53,74,20,103,76,22,56,83,29,91,85,86,88,65],calctypenam:64,add_llvm_loadable_modul:60,tmp9:[5,102],atyp:102,isconvertibletothreeaddress:6,reciproc:70,evalu:[30,68,32,46,70,66,38,39,8,41,54,45,2,47,48,11,12,13,14,15,18,19,52,102,74,64,29,40],lastchar:[39,41,54,43,45,2,47,48],intregsregclassid:52,fourinarow:33,rule:[30,68,31,32,33,93,4,70,6,95,41,5,97,9,46,47,10,99,13,16,50,19,101,53,103,76,102,84,86,25,65,115],acloc:23,tok_var:[39,45],arctan:91,hash_set:16,getjmp_buftyp:68,futur:[68,31,70,41,43,46,47,98,49,13,15,16,17,19,102,74,103,76,56,60,29,84,25,88,111],rememb:[68,73,33,35,70,39,54,97,9,47,45,13,15,16,18,102,20,76,23,24,84,25],parse_id:[12,13,14,15,18,19],iplist:16,tmp2:[15,45],stat:
 [96,40,83,33,75,76,77,80,4,16],addrequir:76,cmake_build_typ:60,ctlz:70,dw_tag:103,stab:103,same_s:22,dyld:71,stai:[32,91,25,90,37],sphinx:[23,105,60,87,37],"_ztv3foo":5,indirectli:[68,70,86,115],bcc:52,portion:[66,23,52,30,112,20,84,83,48,25,107,12,27,70],image_file_machine_sh3dsp:108,perhap:[68,40,74,16,32,70],callingconv:[21,111,52],getpointertofunct:[71,39,45,2,47,48,16],secondli:39,use_bind:[12,13,14,15],"0x29":103,unaryexprast:[39,45,2],parse_var_nam:15,sorri:[38,11],bespok:74,"0x24":103,swap:[29,70,34,78],getllvmcontext:68,preprocess:[61,97],aux:16,downstream:[44,58],"void":[30,91,0,32,46,68,5,66,64,39,8,41,70,97,45,2,47,48,73,84,16,52,102,74,20,103,55,76,78,58,107,29,40,86,63,88,111,54,90,24],llbuilder:15,build_stor:15,appar:[15,45],x86_stdcallcc:111,theier:30,pinvok:29,stageselectioncat:20,image_file_machine_m32r:108,uint32:88,scalarbitsettrait:91,vector:[30,84,0,32,68,70,37,38,39,8,41,54,45,2,47,48,11,49,15,16,19,52,102,20,64,103,78,59,29,91,111],llvm_build_test:60,mllvm:[2
 4,0],initialis:[20,6],whirlwind:[54,18],likeli:3,cpu_x86:91,msdn:68,getposit:20,aggreg:[30,59,52,16,46,103,68,49,70],binop_preced:[12,13,14,15,18,19],dw_apple_property_unsafe_unretain:103,even:[84,0,32,33,1,35,68,4,70,6,38,45,96,40,5,43,9,2,47,48,10,11,49,73,12,14,15,16,17,101,74,99,76,21,80,58,23,24,91,110,111,65,27,105,90,29,115],rope:16,fcur:32,addllvm:60,neg:[52,102,5,103,25,111,107,70],asid:[70,16],transcrib:[41,19],nex:76,libpo:20,"new":[30,61,91,31,32,101,1,46,68,69,4,98,70,71,37,38,39,84,8,41,112,97,45,2,47,48,10,11,73,12,13,14,15,16,18,19,52,53,90,20,75,64,103,76,21,56,93,96,23,59,82,83,24,40,85,86,87,63,25,88,54,111,107,65,27,105,28,29,115],net:[113,37,29],ever:[38,68,40,70,29,25,11,26,16],hasglobalalias:32,metadata:[23,25,102,8,74,32,29,43,103,58,10,3,37,39,111,59,30,55,70,17,49],elimin:[30,84,68,70,39,8,54,97,45,2,47,48,49,12,13,14,15,16,18,52,74,20,103,76,77,23,59,83,29,40,63,25],behavior:[30,61,1,68,70,64,40,5,44,45,47,13,15,16,97,18,52,74,20,76,23,107,29,84,86,87,54,2
 4],old_bind:15,mem:[30,12,13,14,15,70,27,18,19],henrik:4,restat:68,met:[32,84,70],valuemap:16,ccassigntostack:52,image_scn_cnt_initialized_data:108,interpret:[73,1,70,6,66,38,39,41,112,44,45,2,47,48,10,11,12,13,14,15,16,18,19,100,74,20,103,78,80,23,60,84,62,88,111,54,26,65,28],dcmake_crosscompil:9,gcname:111,getunqu:16,credit:25,ebenders_test:98,permit:[39,74,70,77,84,45,10,59,22,15,16,115],parlanc:[43,17],prolog:[84,52],fsub:[45,15,70],immin:93,machineregisterinfo:84,quickcheck:16,fcoverag:66,createnvvmreflectpass:8,icc_n:52,call:[30,91,0,54,32,33,46,68,36,4,98,70,6,71,38,39,104,84,8,41,5,43,97,45,2,47,48,10,11,49,73,12,13,14,15,16,17,18,19,66,52,74,90,20,64,103,76,21,22,78,56,80,55,58,96,23,59,82,83,24,40,85,86,62,88,50,111,107,26,27,28,29,115],calm:[15,45],recommend:[68,73,1,8,54,45,46,48,10,12,15,18,102,103,76,23,60,24,84,62,25,65,29],icc_g:52,type:[30,61,107,0,32,33,77,46,35,3,36,101,68,70,6,71,37,7,39,84,8,41,112,43,97,9,2,47,48,10,11,49,45,12,13,14,15,16,17,18,19,66,52,102,74
 ,54,20,38,103,76,21,22,78,56,55,93,96,23,59,60,82,73,83,29,40,108,87,91,25,88,50,111,64,26,65,27,28,110,115],tell:[68,32,33,70,66,38,39,40,41,112,45,10,11,15,16,50,19,102,74,20,64,103,23,60,83,84,87,62,25,18,54,65,90,115],esi:[84,6],"__eh_fram":84,columnend:66,warn:[30,68,33,93,35,5,6,64,39,96,70,16,20,21,23,60,29,84,25,26,65,28,115],all_build:35,wari:49,jitcompilerfunct:52,gpl:[25,97],dw_tag_apple_properti:103,room:[76,54,18,56],rightr:32,floattyp:16,dw_apple_property_nonatom:103,setup:[38,39,101,52,41,103,10,63,11,22,16,19],functionnam:[74,70],v8deprecatedinst:52,librarygroup:26,root:[23,100,25,60,113,53,41,29,1,9,103,87,10,74,21,59,26,84,70,50,19],clang_cc1:[10,5],defer:[12,32,71,48],give:[30,91,32,68,70,66,38,39,8,41,43,97,9,2,48,11,49,73,14,84,16,17,19,52,20,103,76,23,83,24,40,86,25,111,113,27,105,28],dlsym:[12,65,76,48],ocaml:[29,12,13,14,15,17,18,19],binpath:98,subtmp5:[15,45],dragonegg:[37,97,25,84,93],unsign:[91,0,32,68,3,70,66,39,8,41,45,2,47,48,84,16,19,52,102,74,20,103,2
 1,24,40,111,90],secidx:22,quot:[20,91,103,10,26,70,115],tbaa:[59,70,49],dependfil:65,answer:[30,68,102,37,32,20,40,45,47,48,49,105,12,13,15,70,29,97],registerlist:52,config:[1,67,4,39,41,97,45,2,47,48,10,16,50,19,100,52,53,113,23,60,24,87,25,26,65],confid:25,reloc_absolute_word:52,attempt:[71,30,75,52,40,107,112,29,65,87,83,76,68,88,111,23,4,84,70,97],unnamed_addr:[70,111],"0x7fffe3e85ca8":24,maintain:[64,68,40,74,70,20,84,103,86,76,25,88,111,32,4,16,6],yourregex:5,vfp:[34,78],decl:6,mo_registermask:84,privileg:[4,70],gcda:94,clangstmtnod:21,unexpetedli:10,sigplan:[74,84],better:[30,61,0,32,33,68,5,38,70,45,47,98,11,13,15,16,18,76,59,24,84,86,54,29],argti:70,persist:[24,16],erlang:70,vmcnt:72,newtoset:68,dummytargetmachin:52,promin:[10,33],overestim:70,promis:25,then_:[13,14,15],llvmlinux:29,usertarget:65,"0x7f":[70,115],mapsectionaddress:71,isel:[84,59,115,52,114],"instanceof":16,grammat:[54,33,18],grammar:[64,54,24,2,14,18],meat:12,build_for_websit:93,setdescript:20,getvalu:[68,16
 ],somefancyaa:76,went:[13,47],thenv:[39,45,2,47],side:[30,84,8,41,70,29,40,2,47,10,74,68,54,32,13,14,73,16,18,19],bone:[88,52],mean:[30,84,32,1,93,68,101,4,70,6,38,39,96,40,41,5,43,45,46,47,48,11,73,12,13,15,16,17,50,19,52,102,74,20,99,103,76,110,22,78,23,60,90,91,63,25,111,107,65,28,115],rev64:78,awri:65,add_ri:115,crit:30,taught:84,f108:8,f107:8,extract:[66,30,7,96,52,16,29,103,67,35,21,73,70,6,115],getsextvalu:16,unbound:[84,70,52],crucial:70,content:[30,68,32,33,67,94,36,70,6,37,96,40,101,5,10,12,13,14,15,16,17,18,19,51,52,53,20,103,76,22,78,89,60,90,84,25,111,112,26,65,105,28],dw_lang_c99:103,mtripl:[70,77,5,80],dfpregsregclass:52,reader:[64,68,32,91,67,111,54,57,70,97,18],end_cond:[13,14,15],umul:70,parseforexpr:[39,45,2,47],nodetyp:52,linear:[23,102,40,84,76,77,80,16],parse_definit:[12,13,14,15,18,19],mytyp:70,verif:[73,30,20,70,72],situat:[30,101,52,0,16,20,84,86,48,76,63,107,32,12,65,102,70],infin:70,parenthesi:[54,68,18],insttoreplac:16,getfunctiontyp:16,retcc_x86_32_fast:
 52,dw_at_rang:103,nummodulevalu:111,typesaf:70,ish:[14,2],isn:[30,68,4,70,39,41,54,43,97,47,48,12,13,83,17,18,19,102,76,79,16,84,86,109,25,65],isa:[37,68,104,101,52,74,29,84,72,16],getinstrinfo:[84,52],isd:[64,84,52],cpuinfo:34,floorf:0,my_kernel:8,targetregistri:[84,52],hook:[13,84,83,50,47],unlik:[30,68,73,70,45,48,12,15,16,101,74,76,23,107,29,84,86,63,25,88,111,65,28],featureb:91,featurec:91,featurea:91,agre:[30,25,91],payload:84,hood:[10,66],global_empti:16,tsc701:52,specialis:70,ieee754:70,sometim:[23,25,111,101,52,30,5,20,91,68,83,10,21,70,32,65,102,84,16,97],sphinx_output_html:60,arm_apcscc:111,dwell:41,filepo:20,llvm_enable_pedant:60,bodyv:[39,45],a32:78,namespac:[39,60,52,41,54,20,45,2,47,48,76,74,68,111,16,6,103],build_cond_br:[13,14,15],direct:[84,0,31,32,1,5,93,68,4,70,6,112,45,49,15,16,52,20,103,76,22,59,60,29,91,88,65,114,115],isascii:[39,41,54,45,2,47,48],buildmod:[10,65],dllvm_tablegen:9,ri_inst:115,symptom:23,enjoi:113,r14d:6,silli:[43,68,17,97,40],r14b:6,keyword:[6
 8,0,70,6,66,39,40,43,45,2,47,10,13,14,15,17,102,20,76,29,84,28,115],mcdesc:52,r14w:6,matter:[64,68,86,76,25,88,12,70],emitjumptableaddress:52,pointkind:74,modern:[23,38,68,104,0,43,97,98,10,11,65,16,17],mind:[68,54,45,25,15,16,18],stackar:74,bitfield:86,seed:[24,42],seen:[38,68,52,73,70,20,84,2,48,76,11,111,32,14,16],seem:[84,60,101,40,74,32,20,44,78,102,83],seek:[30,60,37,29,102,25,22,65],minu:[85,70],ty2:[64,70],memcheck:[10,1],image_sym_class_register_param:108,preincrement:68,rethrow:107,myset:68,myseq:91,distsourc:65,fnstrart:84,cudevic:8,regular:[23,7,68,96,33,70,20,91,38,86,11,29,32,65,5,24],ccassigntoreg:52,secrel32:22,tradit:[23,30,43,84,103,76,110,16,17],simplic:[41,43,74,88,16,19],don:[30,61,0,31,32,33,1,93,68,4,70,66,38,39,84,8,41,5,43,97,45,2,47,48,10,11,49,12,13,14,15,16,17,18,19,101,102,74,20,103,76,80,23,82,40,62,25,54,65,105],pointe:[70,111],dom:30,pointi:91,alarm:34,obtus:102,dog:20,expandinlineasm:52,digress:[14,2],dot:[30,93,16,103,65],"0xffff000000000002":88,hun
 ger:[38,11],visitor:[64,41,29,17,74,21,83,43],esoter:115,llvm_enable_werror:60,syntax:[84,73,68,70,6,37,39,8,41,5,43,97,45,2,47,48,10,12,13,14,15,17,18,19,102,20,103,21,22,80,23,59,29,91,108,77,88,54,65,27,105,28,115],selftl:24,errstr:[39,45,2,47,48],test_fuzz:24,istruncatingstor:52,despit:[73,20,84,103,76,99,6,115],acquir:[70,86],machineinstr:[80,77,21,84,52],explain:[37,68,60,96,40,32,43,84,45,76,85,78,15,16,17,97],sugar:[29,70],regnum:88,"__nv_truncf":8,pinst:16,hasgc:32,stop:[23,64,68,60,74,16,44,76,54,107,70,97,18],compli:74,smul:70,bar:[68,0,1,70,66,8,41,5,97,46,47,10,13,84,16,19,20,103,55,22,60,29,91,28],x86_mmx:70,sacrific:[32,70],baz:[68,0,20,103,47,13,28,29],reload:[84,15,45,39,59],bad:[112,39,31,70,91,68,2,103,83,32,4,14,16,97],dw_tag_shared_typ:103,bam:68,addinstselector:52,flagpointi:91,cstdio:[39,41,54,45,2,47,48],instalias:84,"0x40":103,"0x42":111,"0x43":111,msan:24,subject:[84,68,25,16],p1i8:8,said:[38,68,107,103,11,16],simplest:[84,52,41,54,20,91,48,35,12,18],attrib
 ut:[30,32,69,70,6,37,8,44,46,16,52,74,20,103,21,77,56,80,29,85,25,111,90],add_memory_to_register_promot:15,triplet:[20,70],howtousejit:100,lazi:[70,29,40,16,30],abs_fp80:6,configurescript:65,imagmag:[14,2],against:[23,100,25,60,96,101,8,5,24,91,46,10,62,3,70,107,30,16,33,97],fno:0,uni:8,readnon:[30,8,73,103,55,49,111,70],constantindex:88,uno:70,foobaz:68,createload:[39,45],devbufferc:8,devbufferb:8,devbuffera:8,foobar:[91,68],int32_t:[74,91],"16b":78,loader:23,theoret:[4,16],"__________________________________________________________":16,performcustomlow:[74,29],three:[30,31,32,33,5,112,97,47,10,73,83,18,52,102,54,20,55,76,21,70,23,16,24,84,87,111,107,65],objc_properti:103,specul:[107,86,70,49,40],succ_begin:16,trigger:[71,7,91,60,40,74,83,29,61,10,68,88,70,33],interest:[30,84,73,33,1,67,35,68,36,70,71,37,38,39,40,41,5,43,97,45,2,47,48,10,11,12,13,14,15,16,17,18,19,101,74,20,103,76,78,23,107,24,91,86,25,54,113,29],basic:[30,84,0,32,33,67,93,94,35,68,36,101,4,70,6,97,66,38,39,96,8,41
 ,54,43,44,45,2,47,48,11,49,99,12,13,14,15,16,17,18,19,52,102,74,20,103,76,77,56,58,23,59,60,61,86,88,50,111,105,28],tini:[32,101],llvmpassnam:60,build_load:15,deeper:[105,101],suppress:[74,68,1,70],mce:52,sparsemultiset:16,multithread:[74,76,16],lpae:86,lpad:70,argumentexpr:[12,13,14,15,18,19],llvm_include_test:60,terminatorinst:[68,3,16],ugli:[16,14,97,5,2],subsequ:[71,30,102,52,0,29,84,103,88,27,70,20,115],intregsvt:52,itinerari:[84,6,52],noredzon:[70,111],slt:70,servic:[4,97,40],lex_id:[12,13,14,15,17,18,19],slp:[59,0],calcul:[76,30,59,52,40,70,33,84,103,47,10,13,102,16,58],typeflag:103,occas:68,sle:70,anchor:[68,103],r600:[23,104,72,87,37],gninja:24,folk:24,uncopy:68,xxxkind:101,disappear:[23,97,34],grown:[14,11,2,38],receiv:[71,16,24,111,107,70,6,18],make:[30,61,0,31,32,33,1,34,46,68,101,4,98,70,6,66,37,38,39,84,8,41,5,43,97,9,2,47,48,10,11,49,45,12,13,14,15,16,17,18,19,100,52,53,74,20,99,103,76,113,77,78,102,93,96,23,105,60,82,73,83,24,40,86,87,91,62,63,25,88,50,111,54,26,65,1
 14,90,29,115],bitmask:70,who:[66,23,38,68,52,37,32,61,45,62,10,25,11,26,4,15,70],isspac:[39,41,54,43,45,2,47,48],initialexec:[70,111],kevin:84,codeemitt:21,ssl_ctx_new:24,zlib1g:9,kib:20,overs:16,revector:[30,16],binopprototyp:[14,15],qualif:93,vehiclemak:68,ea_r:84,"00clang":103,addrawvalu:56,inherit:[76,68,101,40,16,20,84,62,21,4,28,6,115],llvm_dir:[32,60],endif:[66,38,39,20,68,11,4],programm:[72,37,38,39,101,0,74,28,20,75,2,83,76,68,11,86,65,14,84,16,29],paradigm:[29,16,102],left:[30,68,0,32,33,70,6,39,96,41,54,47,13,84,83,18,19,52,103,29,91,111],projusedlib:65,op0:111,op1:[70,111],op2:70,op3:52,bandwidth:70,human:[92,23,68,95,106,30,32,91,76,36,89,70,6],nowadai:9,yet:[30,68,32,33,46,70,71,2,47,48,72,12,13,14,16,100,52,74,20,76,113,23,24,84,87,26],languag:[30,84,0,73,68,70,6,37,7,39,95,8,41,5,43,97,45,2,47,48,10,11,49,92,12,13,14,15,16,17,18,19,51,52,102,74,20,75,38,103,77,104,23,106,107,24,91,86,87,25,88,54,115,28,29,99],uint16:88,save:[84,0,46,35,36,70,71,64,39,8,45,2,47,48,12,
 13,14,15,16,52,20,103,78,23,60,82,107,29,61,62,88,111,24,115],vpsubusw:10,u999999:82,applic:[68,32,33,94,70,6,71,37,38,104,96,43,2,48,10,11,49,73,12,14,16,17,100,52,74,20,76,78,60,107,24,84,25,88,111,26,65,115],segnam:20,background:[66,101,84,98,21,105,16],opc:[39,45,2,115],wojciech:30,fact1:32,fact0:32,getinstlist:16,manual:[68,0,70,6,37,38,104,101,10,11,49,83,52,102,20,75,103,76,23,60,16,29,84,25,113,65],dindex:52,tolmach:74,machinepassregistrynod:76,choic:[92,38,68,73,16,24,34,47,88,77,11,64,13,70,43],jumptabl:70,unnecessari:[30,68,84,16,52],cxxflag:[100,39,41,45,2,47,48,65],www:[24,93],deal:[30,68,111,101,107,45,103,86,21,25,78,15,16],global_ctor:[97,70],interv:[23,84,16,30],somehow:[76,16],dead:[30,59,23,16,20,8,40,103,76,90,49,73,84,70,97],type_code_fp128:111,intern:[30,91,84,33,1,68,4,70,6,71,37,39,8,41,112,97,45,49,15,16,19,66,52,102,20,103,55,76,21,89,79,23,60,107,40,87,111,65,90,115],interg:66,make_pair:[32,39,45],norman:84,insensit:40,collect:[30,68,0,73,33,94,70,71,37,38
 ,104,40,43,11,49,16,17,74,20,103,56,58,59,24,88,65,90,29,115],henderson2002:74,tracker:25,genrat:60,getchar:[39,41,54,43,45,2,47,48],xmm15:6,creatur:[14,43,2,17],burg:59,idiomat:[10,68],bold:105,identifierexpr:[39,41,54,45,2,47,48,12,13,14,15,18,19],uncompress:[23,16,60],cdt4:23,mappingnorm:91,buri:68,strippointercast:68,promot:[30,64,39,52,40,16,84,45,25,49,59,15,70],burr:80,"super":[84,90,52],fnty:70,unsaf:[38,103,86,88,77,11,80,70],dw_tag_formal_paramet:103,movsd:5,argv0:80,culaunchkernel:8,ppcf128:70,compilecommonopt:65,simul:[84,70,78],movsx:84,commit:[23,59,82,37,73,24,68,93,10,25,49,113,105],marshal:88,movsq:84,mrm7m:52,contriv:[97,115],f128:[70,52],down:[30,84,32,6,66,37,38,39,101,40,112,2,47,11,13,14,16,18,52,102,54,20,103,76,77,78,80,23,82,83,24,61,62,25,107,65,29],f3_12:52,indexreg:84,mrm7r:52,nomodref:40,insidebundl:84,subl:[84,5],parsesubtargetfeatur:52,precomput:40,perldoc:23,frameinfo:52,xpass:1,imit:[105,28],ssl_do_handshak:24,r173931:21,fraction:[69,24,58,101],amazi
 ngli:[13,47],"_els":[39,45,2,47],fork:[4,24],numxform:16,creation:[71,52,74,16,93,56,70],form:[30,61,107,91,32,33,68,69,70,6,71,37,38,101,84,8,41,5,43,97,45,47,48,10,11,49,73,12,13,15,16,17,18,19,52,53,74,54,20,103,76,22,89,102,96,23,59,60,82,90,40,25,88,111,112,65,28,115],sub1:5,forc:[23,68,60,0,107,20,91,9,46,103,76,88,80,65,70],retarget:[37,84],nounwind:[8,5,103,55,10,49,111,70],phid:68,emitbyt:52,autoinsert:16,inttoptr:[88,70,49,102],bugfix:93,writeattribut:21,processrelocationref:71,llvma:65,multisourc:[10,33,25,103,61],dontcopi:68,f88017:84,"__i386__":[38,11],unrel:[25,16,52,93],classid:28,classif:[4,70],featur:[30,84,0,31,32,33,1,46,68,69,4,70,6,66,37,38,72,54,97,45,2,47,10,11,73,13,14,15,16,18,52,74,20,103,76,21,93,23,82,24,91,62,25,50,65,90,29],semicolon:[39,60,115,41,54,45,2,47,48,12,13,14,15,18,19],classic:29,consciou:23,visitgcroot:74,diagnost:[44,0,29,1,21,5,6],glanc:[38,68,11],ship:[23,38,29,87,98,11],dwarfnumb:52,excel:[23,16,52,40],image_scn_align_2048byt:108,stackre
 stor:[70,46],journei:[15,45],subdivid:33,why:[68,73,70,39,40,54,43,97,45,47,32,13,15,16,17,18,101,102,99,103,76,21,24,91,63,25,65,105],"0fc2d20000":8,iteri:[12,13,14,15,19],disttargzip:65,libffi:62,setinsertfencesforatom:86,uclibc:29,pseudo:[66,52,16,84,103,76,21,78,26,114,70,58],dcommit:23,image_sym_type_int:108,include_directori:60,skip:[68,0,70,66,39,41,54,43,45,2,47,48,12,13,14,15,17,18,19,52,103,78,84,111],"0x00000150":103,inlineasm:32,skim:68,createvirtualregist:84,mill:20,primer:105,pldi:74,hierarch:[30,111],misread:68,libit:20,depend:[30,84,0,31,32,33,1,68,3,36,69,4,70,71,45,96,8,41,112,97,9,10,49,73,15,16,18,19,100,52,102,20,75,103,76,113,22,56,23,107,29,40,86,87,62,25,88,50,111,54,26,65,24],fancier:[76,105],intermedi:[37,7,97,60,106,52,31,16,75,46,74,54,111,56,73,70,18],targetinstrformat:52,hasinternallinkag:16,image_scn_align_2byt:108,letitem:28,mandlebrot:[14,2],llvmbuilder:12,aspx:68,llvmdummycodegen:52,string:[30,84,1,68,3,69,4,70,6,66,64,39,96,8,41,5,43,45,2,47,48,12,
 13,14,15,16,17,18,19,52,20,103,55,76,21,56,79,80,23,60,24,91,109,77,111,54,26,27,28,29,115],create_argument_alloca:15,kernel_param_2:8,kernel_param_0:8,kernel_param_1:8,print_endlin:[12,13,14,15,18,19],dil:6,did:[38,68,101,40,70,97,45,2,48,76,107,11,32,12,14,15,16],die:[30,39,103],dif:30,dig:[43,17,115],iter:[30,84,0,32,68,70,71,40,54,45,2,47,13,14,15,16,18,52,74,90,20,58,59,83,91,25,28,115],item:[23,111,96,115,73,32,20,91,45,103,29,78,36,26,65,15,24,49],div:[84,16],round:[66,84,91,2,103,78,14,93,70],dir:[23,60,31,24,1,9,103,87,94,65,50],sparclit:52,originput:20,nozero:80,sideeffect:70,addr:[79,70,52],addq:88,insertbranch:52,favour:[6,99],addx:115,wors:[84,68,78],rephras:102,addi:115,xml:111,dwarf:[66,38,39,52,74,90,84,103,67,98,107,11,89,88,16],oversimplifi:16,elsev:[39,45,2,47],slow:[62,76,24,77,16],imul16rmi:84,wait:[68,31,54,72,113,4,18],patleaf:52,insan:68,canadian:[23,87],shift:[30,64,32,20,84,58,111,70,6],bot:[37,25,68],"_ztii":70,storeregtoaddr:52,extrem:[23,84,52,30,16,24,4
 0,45,103,83,76,25,111,86,69,15,70,28,115],bob:91,else_:[13,14,15],opcstr:52,stb_local:70,maxnum:70,modul:[30,84,32,33,1,67,93,68,36,70,71,7,39,8,41,44,45,2,47,48,10,12,13,14,15,16,97,19,52,74,75,103,55,76,23,59,60,83,40,88,111,65,90],mdlocat:[29,70],"__jit_debug_register_cod":98,copyvalu:40,patchabl:88,"0baz":16,"0x60":96,"0x800":103,sake:[76,16],allocinst:15,getsubtargetimpl:[74,52],visit:[74,83,64,16],tokidentifi:28,deplib:111,perl:74,everybodi:[32,25],zeroargfp:115,checkout:[10,23,31,62,87],rpath:[23,29],fcomi:84,com_fir:84,appel:74,indic:[30,68,0,73,33,1,3,36,101,70,6,66,37,39,96,40,41,54,47,10,49,13,16,18,19,52,102,74,20,103,76,22,78,56,58,59,60,107,84,25,88,111,26,65,28,115],examin:[71,52,83,20,84,93,10,94,16,29],effort:[71,30,64,68,41,97,103,25,88,4,19],armhf:9,fly:[54,29,84,48,12,18],reviewe:25,ulp:70,uniqu:[91,111,84,0,41,5,29,56,103,69,90,88,70,32,26,73,16,6,19],ult:[45,47,12,13,14,15,70,19],sourcewar:63,imped:70,nextvar:[39,45,2,47,13,14,15],nearest:[66,70],basic_block:19
 ,predict:[76,37,3,68,49],crazi:[20,43,11,17,38],subregion:70,fp16:70,dominatortre:76,exctype1:107,strikingli:[14,2],delete_funct:[12,13,14,15,19],subnorm:8,binarypreced:[39,45,2],"0x000034f0":103,targetsubtarget:[84,52],ping:[32,25],f32:[84,70,52,8],idiv:84,brain:68,till:[113,16,98],getdatalayout:[39,52,74,45,2,47,48],purg:68,attrparserstringswitch:21,pure:[30,59,52,41,73,84,103,25,26,28,19],doclist:91,testingconfig:1,map:[91,0,32,1,94,68,69,70,71,37,64,39,84,8,41,54,45,2,47,48,73,12,13,14,15,16,19,66,52,74,20,103,21,59,40,108,88,111],exctypen:107,max:[66,20,1,70],usabl:[52,20,84,77,16,29],intrus:[70,16],mac:[23,96,98,76,93,16],mag:70,mai:[30,91,107,0,32,33,1,68,34,46,94,35,3,4,70,6,71,7,84,8,41,5,43,97,45,2,47,98,10,11,49,73,13,14,15,16,17,50,19,52,102,74,20,38,103,76,113,77,78,56,80,110,93,96,23,59,60,112,24,40,86,87,83,63,25,88,111,64,26,65,90,29,115],uselistord:70,underscor:[65,68,103],maj:31,grow:[70,20,84,46,47,13,27,16],man:[10,23,20,60,37],noun:68,"0x00001000":103,"switch":[
 30,68,0,34,93,3,69,70,64,39,101,41,54,45,2,47,48,12,13,16,19,52,74,20,21,23,107,91,63,65],myglob:103,targetframeinfo:52,purifi:61,str1:115,talk:[38,68,41,54,43,45,64,47,48,76,11,12,13,15,17,18,19],image_sym_class_automat:108,abbrevop0:111,abbrevop1:111,config_fil:65,shield:[4,84],iptr:70,comdat:[70,29,22,111],"123kkk":20,recoup:111,nbsp:84,gcmetadata:74,pointer:[30,91,0,32,46,68,70,71,38,39,84,8,54,43,97,45,2,47,48,11,49,73,12,13,14,15,16,17,18,66,52,102,74,103,55,76,21,59,107,29,40,86,77,88,111,90],entiti:[68,16,103,88,111,70,115],armneontest:21,group:[30,68,32,33,4,70,6,66,37,38,96,5,10,11,18,52,20,103,76,21,29,84,25,54,26,115],monitor:40,polici:[23,68,40,37,25,16],shadowstack:74,build_shared_lib:60,mail:[23,38,68,82,37,31,29,25,11,113,105,50],inlinehint:[70,111],main:[30,68,32,46,94,35,98,70,6,66,37,38,39,8,41,54,45,2,47,48,10,11,12,13,14,15,16,18,19,74,20,103,55,76,78,79,93,58,23,107,24,84,63,25,26,105,90,29,115],irbuild:[39,41,45,2,47,48,12,13,16,19],recoveri:[39,41,54,45,2,47,
 48,12,13,14,15,18,19],parseunari:[14,39,45,2],remateri:86,synopsi:[92,1,5,94,36,42,7,95,96,112,44,100,53,20,75,77,79,80,57,106,109,110,89,114],sooner:113,initv:[39,45],possess:[66,16],lo16:84,subproject:[23,29,25,93,37],xlc:23,careless:68,x11:16,myflag:91,misbehav:31,loopunswitch:30,ndebug:[62,20],continu:[68,33,5,70,38,40,54,98,10,11,16,18,101,20,82,107,84,85,25,111,112,90],gcread:[74,70],redistribut:[25,97],libgcc:85,tmp8:102,recogn:[30,39,33,43,32,20,84,47,90,13,70,17],tmp7:[5,102],tmp6:102,tmp1:[68,5],tmp3:5,baselin:[84,93],getbinarypreced:[39,45,2],announc:[31,37,93],"3rd":70,mess:[23,30],pocl:29,numval:[39,41,54,43,45,2,47,48,111],dw_tag_unspecified_typ:103,arminstrinfo:52,correct:[30,84,0,31,73,33,93,68,4,70,64,40,97,9,48,10,12,16,20,103,76,78,23,59,60,29,61,85,86,63,25,113,65],earlier:[26,66,70,49,52],"goto":[39,0,32,45,2,47,68,15],tmpb:[39,45],ori:84,segmentreg:84,org:[23,39,60,82,37,31,24,63,9,87,91,10,41,35,25,113,68,93,33,19],ord:70,befor:[30,61,0,31,32,33,46,35,68,101,7
 0,71,38,39,84,8,41,5,43,97,9,2,47,48,10,11,45,12,13,14,15,16,17,18,19,52,102,74,54,20,75,64,103,76,21,78,80,93,96,23,60,73,83,24,40,86,91,25,88,107,65,29,115],frequenc:[37,3,58],sn_mapr:32,createasmstream:84,thing:[30,91,32,33,1,93,35,68,4,70,66,38,39,84,40,41,5,43,97,9,2,47,48,10,11,49,45,12,13,14,15,16,17,18,19,102,74,20,103,76,21,78,23,83,61,62,25,50,111,54,26,65,27,105,115],sn_mapl:32,principl:[68,104,32,43,4,17],think:[66,38,84,60,101,8,43,40,68,64,47,25,11,13,69,4,102,16,17],frequent:[23,39,60,102,30,74,70,20,97,68,35,25,37,99,4,16],first:[30,61,91,32,33,1,68,46,94,35,3,69,4,54,70,6,71,38,39,84,8,41,5,43,97,45,2,47,48,10,11,73,12,13,14,15,16,17,18,19,66,52,101,74,90,20,75,103,55,76,78,80,102,93,96,92,23,59,60,83,24,40,86,25,88,50,111,107,113,65,27,105,28,29,115],carri:[70,27,16,96,102],fast:[68,52,16,77,84,45,34,103,76,21,49,32,15,70,105,114],oppos:[23,59,28,20,110,13,70,50],numop:[111,52],const_iter:16,indiviu:84,indivis:46,numindic:66,averag:[13,47,36],daunt:60,clangsacheck:
 21,"0f42d20000":8,my_kei:68,attrkind:[21,56],foldingsetnod:16,getpredopcod:69,vbr6:111,vbr4:111,vbr5:111,vbr8:111,redefinit:[39,41,45,2,47,48,12,13,14,15,19],valuedisallow:20,were:[30,84,0,32,1,35,68,5,6,66,38,70,46,11,16,53,20,75,103,78,23,24,61,86,65,29],lcpi0_0:10,mcexpr:84,mrm5m:52,dw_tag_set_typ:103,licm:[30,59,40,86,76,49,16],llvmlibsopt:65,dash:[20,91],mageia:23,greet:115,gettargetlow:52,exclud:[112,84,25,69,65,5],mrm5r:52,repeatedli:70,unadorn:70,weak_odr:[70,111],squar:[26,91,70,101],advic:[37,112,34,62,25,83],cumoduleloaddataex:8,llvm_target:[12,13,14,15],"_crit_edg":70,advis:[13,93,96,47,56],interior:[59,101],immsext16:84,channel:37,sparciseldagtodag:52,llvm_analysi:[12,13,14,15,19],ptrloc:[74,70],pain:[20,16,98],ldststoreupd:84,trace:[76,73,20,59,103],normal:[84,0,73,1,68,4,70,7,95,96,5,2,49,92,14,16,20,75,103,76,21,78,110,23,60,106,107,91,85,86,87,25,88,111,65,27,90,115],track:[30,84,32,1,68,6,39,40,41,97,45,2,73,14,15,16,19,74,103,76,23,83,24,61,25,88,29],c99:[70,22],n
 establ:[28,115],cucontext:8,pair:[30,68,73,70,5,39,40,54,45,47,32,13,84,16,18,52,103,78,56,107,91,86],r31:84,isglobaladdress:52,synonym:96,exit_on_first:24,cumodulegetfunct:8,dw_form_:103,rev128:78,maskedbitset:91,llvmgxx:65,isphysicalregist:84,defaultconfig:16,gracefulli:16,lexicon:[37,59],show:[84,0,31,1,94,3,98,70,71,38,8,41,5,43,97,45,2,47,48,11,12,13,14,15,16,17,18,19,66,52,102,20,103,76,110,23,105,24,91,109,63,88,54,114,115],shoe:91,threshold:[30,70],corner:88,getadjustedanalysispoint:40,emitexternalsymboladdress:52,globalsmodref:[76,30,40],dice:16,fenc:[29,68,70,49,86],jite:[37,98],adc64mi32:6,parametr:28,ftest:94,customwritebarri:74,sparcisellow:52,intptr_t:[39,0,45,2,47,48],gep:[30,102,37,32,97,49],variou:[30,91,33,68,69,70,6,71,39,104,8,112,43,47,48,10,12,13,84,16,17,18,66,52,54,75,103,76,21,23,60,82,83,24,40,86,87,111,107,26,65,90,29],get:[30,61,91,31,32,33,67,93,35,68,101,4,98,70,6,71,37,38,39,84,8,41,5,43,97,9,2,47,48,10,11,45,12,13,14,15,16,17,18,19,66,52,102,74,90,20,
 64,103,76,21,78,56,58,23,60,82,73,83,24,40,86,87,25,54,113,65,105,28,115],mung:[30,102],secondari:[25,88],repo:23,emitlabel:84,llvmsystem:65,wheezi:9,inreg:[29,84,70,111,52],gen:[39,8,45,2,47,48,72,114],r10b:6,nullptr:[39,68],yield:[30,102,73,20,111,70,33,16],r10d:6,stupid:83,mediat:40,cmpconstant:32,r10w:6,summari:[30,68,73,33,1,94,36,5,7,39,95,112,45,92,15,100,102,20,75,77,78,80,57,23,82,106,87,109,110,111,65,114],wiki:[23,60],kernel:[37,38,52,8,29,0,11,80,70],setpreservesal:76,"__builtin_setjmp":107,intrinsicsnvvm:8,fmuladd:[70,0],assumpt:[38,39,70,84,68,103,77,11,5],fcmp:[41,45,47,12,13,14,15,70,19],testcas:[41,112,25,19,70,16],patent:25,"0b1001011":115,infinit:[30,24,84,70,40],expandatomicrmwinir:86,allroot:33,innov:29,getmetadata:103,datalayoutpass:[39,45,2,47,48],enumer:[84,52,32,20,91,68,103,21,111,114,16,115],label:[30,68,111,52,8,74,5,84,45,46,47,70,32,13,15,16,58,97],innoc:[13,47],enumem:52,volatil:[30,97,52,40,74,84,86,70],across:[30,0,73,36,70,6,38,8,48,11,49,12,16,20,1
 03,76,78,23,59,84,86,88,26],august:71,parent:[23,68,41,70,1,47,26,13,16,58],fpregsregisterclass:52,frameaddress:70,modref:[115,86,40],parseprototyp:[39,41,54,45,2,47,48],copyabl:16,false_branch_weight:3,llvm_enable_sphinx:60,blocklen:111,audienc:[37,49,52],library_nam:26,litloc:39,p0i64:5,improv:[23,38,82,52,30,74,32,24,1,40,48,76,11,49,107,12,93,70,29],peephol:[64,39,84,45,2,47,48,76,12,13,14,15,16],among:[30,90,84,23,32,8,68,40,87,21,22,49,16],acceler:[38,11,103,93],undocu:68,colspan:84,unittest:60,tsflag:52,getnumsuccessor:68,cancel:107,iscal:[6,115],inadvert:[4,5],mctargetdesc:21,xadd:86,ultim:[68,31,1,48,12,65,70,6],p0i8:[70,8],mark:[66,23,84,52,8,73,16,1,86,98,10,74,68,88,49,111,32,30,27,70,6],certifi:97,"0x4004f4":79,basicaa:[76,30,40],"0f0":84,fadd:[64,52,8,41,84,45,47,48,12,13,15,70,19],squash:[23,78],f92:8,f93:8,f90:8,f91:8,f96:8,f97:8,f94:8,f95:8,univers:[66,68,16,97,25,79,70],f98:8,f99:8,those:[30,84,32,1,34,94,68,36,4,70,6,66,37,39,96,40,5,44,45,10,73,15,16,52,102,74,20
 ,103,76,23,60,83,29,91,86,25,88,107,26,65],sound:[24,40],isvararg:16,interoper:[74,16,38,11,107],desttool:65,"0x3feb":103,"0x3fea":103,invoc:[23,60,112,84,5,83,76,65,70],isdoubl:115,gvneedslazyptr:52,advantag:[38,68,102,74,70,20,84,45,2,86,25,11,78,56,14,15,16,90],mfloat:9,bytecode_libdir:65,destin:[39,96,52,107,84,45,10,3,49,15,70],llvm_gcc_dir:33,variable_op:115,my_function_precis:8,cudeviceget:8,liveoffset:74,same:[30,61,0,31,32,46,94,68,36,69,4,70,6,66,38,95,84,8,41,5,43,97,45,2,47,48,11,99,73,12,13,14,15,16,18,19,52,102,74,20,75,64,103,76,21,22,78,80,93,96,23,59,83,24,40,85,86,87,91,62,63,25,88,50,111,54,26,65,105,29,115],ssl_library_init:24,image_file_machine_unknown:108,pad:[66,96,107,46,88,111,70],emitloadlink:86,pai:[10,25,68,52],oneargfp:115,add32mi:6,exhaust:[23,30,74,24,84,16],assist:[68,61,2,65,14,114],executionengin:[23,39,60,98,84,45,2,47,48,12,13,14,15,16],capabl:[70,38,104,8,41,45,2,48,11,12,14,15,16,19,52,20,64,76,23,84,40,87,90],value_symtab_block:111,executeprogr
 amandwait:4,runonmachinefunct:[76,84,52],appropri:[30,84,31,9,1,93,68,69,4,70,6,64,8,54,45,2,49,73,14,15,16,18,52,74,20,103,76,78,56,23,107,29,40,86,25,113,65,90],macro:[66,23,75,60,52,16,20,91,68,48,76,21,12,70,6],markup:[23,27,68,87,105],spadini:30,getobjfilelow:74,asmnam:52,roughli:[59,101,107,84,86,93],emitleadingf:86,release_22:23,execut:[30,61,0,73,33,1,67,94,35,68,4,98,70,71,37,39,104,84,8,41,112,97,45,2,47,48,10,49,12,13,15,16,18,19,66,52,74,54,20,75,103,76,21,80,110,58,23,59,60,83,29,40,85,86,87,77,88,50,107,65,24],speccpu2000:33,mo1:52,mul_ri:115,mygcprint:74,subblock:111,aspect:[28,38,39,60,41,16,29,84,103,47,74,25,11,54,13,70,18,19],mul_rr:115,asmmatch:21,flavor:[70,16,103,115],"125000e":70,xxxtargetmachin:52,critial:93,param:[68,8,74,1,113,35,12,13,14,15,16,19],cumoduleunload:8,sparcregisterinfo:52,"__cxa_throw":107,dclang_tablegen:9,setrequiresstructuredcfg:52,mcregaliasiter:84,mov:[22,84,5,86,8],coverage_pc:24,va_start:70,libsfgcc1:9,mod:[30,52,40,16,76,70,115],"0x000
 01023":103,llvm_tarball_nam:65,ifstream:8,qnan:70,divari:39,server:[24,16],bb0_4:8,bb0_5:8,prologuedata:111,either:[30,61,32,33,1,93,68,70,6,71,38,39,96,8,54,43,97,47,48,10,11,73,12,13,84,16,17,18,100,52,102,74,20,75,64,103,77,78,79,23,83,24,40,86,63,25,88,111,107,65,29,115],bb0_2:8,physreg:84,nice:[30,68,5,38,41,54,43,45,2,47,48,11,12,13,14,15,16,17,18,19,20,76,23,115],mappingnormalizationheap:91,fulfil:[4,101],exitcod:1,fastcal:[84,70],ascend:[66,70],substitu:10,llvm_enable_doxygen_qt_help:60,adequ:[74,35,60,52],confirm:68,llvmscalaropt:50,recomput:[76,16,40],ffi_library_dir:60,"__llvm_stackmap":88,inject:68,dw_op_plu:103,ret_val:[12,13,14,15,19],broken:[37,97,52,29,1,10,25,78,76,115],fpmath:70,cuinit:8,selectaddrrr:52,cornerston:102,x32:5,dw_ate_address:103,island:[104,72],loadinst:68,image_scn_align_4096byt:108,deopt:73,llvm_targets_to_build:[35,60],lcamtuf:24,livecount:74,terminolog:[23,58,3,39,37],hashtbl:[12,13,14,15,18,19],strip:[23,30,90,20,75,103,87,10,94,65,16],"0x3fe9":1
 03,ymax:[14,2],mingw32:[10,113,84],overwrit:[20,88,50],legalact:52,savethi:5,x86inst:6,dllvm_default_target_tripl:9,addrequiredtransit:76,source_x86_64:79,dw_ate_boolean:103,enough:[68,32,4,70,39,41,54,47,10,13,83,50,19,52,102,20,103,76,60,16,84,85,86,25,88,18,65,27],getmodrefinfo:40,buggi:61,gprc:84,possibl:[30,61,91,31,32,1,68,4,70,71,38,39,84,8,54,43,97,9,46,47,48,10,11,49,45,12,13,15,16,17,18,66,101,102,74,20,64,103,76,21,78,23,60,82,73,83,29,40,85,86,87,63,25,111,65,27,105,90,24,115],testoneinput:24,optnum:20,poolalloc:40,unusu:[38,74,84,85,11,65,16],sanitize_address:70,embed:[66,30,60,74,70,29,104,2,47,103,25,111,13,14,16],i32mem:115,emitpseudoexpansionlow:21,machinefunctioninfo:84,emitloc:39,threadloc:[70,111],subprogram:[39,103],deep:[30,68,101,105],simpletyp:108,calledcount:83,file:[0,1,3,4,5,6,7,8,9,10,12,15,16,17,20,21,23,112,24,25,26,27,28,29,30,31,32,33,35,36,37,64,39,41,42,43,44,45,2,47,48,50,66,52,53,57,60,91,63,65,61,67,69,70,71,73,75,76,77,79,80,106,83,84,87,89,90,6
 8,92,93,94,95,96,97,98,99,100,103,104,105,82,108,109,110,111,54,114,115],emitvalu:84,release_xyz:93,proport:[65,20],fill:[39,40,41,16,20,61,45,2,47,48,76,68,54,113,91,70,43,103],again:[32,33,93,70,38,41,5,45,47,48,11,12,13,15,16,20,76,78,107,29,61,85,105,24],mangler:52,field:[68,73,1,69,70,66,38,96,40,54,11,49,32,16,18,52,102,74,103,21,29,91,110,88,111,28,115],xxxgeninstrinfo:52,"0xc0de":111,riinst:115,architectur:[31,1,34,93,35,70,6,37,104,8,5,9,10,49,51,52,77,78,79,80,23,60,29,84,86,21],reextern:[39,41,45,2,47,48,12,13,14,15,19],formed:70,"0th":102,sequenc:[30,84,0,73,68,5,66,40,70,45,2,32,14,15,16,18,52,102,74,76,21,78,80,107,91,108,88,54,28,115],ilist_trait:16,arrayidx:70,unload:[76,70],descript:[30,61,32,1,67,94,68,36,5,6,66,37,7,39,95,96,8,101,112,44,42,92,84,16,100,52,53,20,75,103,113,21,70,89,79,80,57,110,23,82,106,83,29,40,108,86,87,109,77,88,111,107,26,65,114,90],v2f64:70,version_less:60,escap:[23,40,28,5,2,10,74,90,14,70,27],getreturntyp:16,unset:[39,28],represent:[84,73,
 68,70,6,66,37,38,40,41,54,97,2,48,11,12,14,16,18,19,52,74,20,103,76,78,58,59,29,91,88,64,27,115],insertbefor:16,forget:[74,39,68,101],mrm3m:52,forbidden:[76,4,68],dollar:34,dw_form_ref2:103,sunk:40,llvmdummyasmprint:52,dw_form_ref1:103,regno:84,mrm3r:52,dw_form_ref8:103,children:[65,101],edg:[37,30,5,84,83,76,70,58],image_sym_class_clr_token:108,at_byte_s:103,insertion_block:[13,14,15],daniel:103,brtarget8:52,immt:6,image_scn_lnk_comdat:108,r14:[84,6],r15:[84,6],r12:[84,22,6],r13:[84,6],r10:[84,85,6,8],r11:[85,70,6,88],fals:[30,68,45,1,34,3,69,70,39,101,40,41,112,97,9,2,47,48,32,13,16,52,74,20,103,76,21,80,23,83,65,90],offlin:[29,84,8],util:[30,0,31,67,35,36,6,37,96,40,16,52,53,74,20,21,80,110,23,91,109,25,26,65],fall:[30,39,52,74,16,20,45,2,47,48,68,70,12,13,14,15,5,58],"0x629000004748":24,type_code_integ:111,basereg:84,run_funct:[12,13,14,15],gcno:94,use_end:16,stderr:[30,39,41,54,45,2,47,48],"__sizeof_int128__":29,"7fca9f":66,webkit_jscc:[70,111],rawfrm:[52,115],globalalia:76,law
 yer:25,val2:70,val1:70,val0:70,excit:[38,11,29,93],parsedattrinfo:21,excis:70,abi:[30,34,93,70,38,39,104,96,8,97,9,46,48,10,11,12,52,103,22,78,23,107,29,84,62],worthwhil:16,abl:[91,0,32,46,70,66,38,39,96,40,5,97,9,2,47,48,11,49,73,12,13,14,84,16,52,102,74,20,103,76,23,59,83,29,61,25,88,26,105,90,115],invok:[30,84,32,68,70,71,8,5,45,46,48,10,49,12,15,16,18,52,74,54,20,76,23,60,83,29,40,87,88,111,107,65,90],abu:96,g0l6pw:23,hurdl:97,"public":[68,31,93,37,39,52,8,41,54,45,2,47,48,16,101,74,20,103,76,113,23,91,25,26],exit5:8,cumemcpydtoh:8,valc:8,variat:[52,40,0,84,4,105],vala:8,sophist:[74,33,84,76,105,70],analysisusag:[76,40],memory_order_acquir:[70,86],movsx16rm8w:84,xemac:[23,65],valu:[0,1,2,3,5,6,7,8,10,11,12,13,14,15,16,17,18,19,20,21,23,29,25,26,28,30,32,33,35,36,37,38,39,40,41,54,43,44,45,46,47,48,49,50,52,53,56,59,60,91,64,65,69,70,66,72,73,74,75,76,77,78,80,84,85,86,87,88,68,92,95,96,97,98,100,101,102,103,106,107,108,109,111,112,114,115],quieta:20,search:[30,0,73,1,69,5,37,70,
 47,32,13,16,50,52,74,20,103,23,59,60,83,107,26,65],unabbrevi:111,image_rel_amd64_sect:22,createfcmpon:[39,45,2,47],r12w:6,r12b:6,val_:15,r12d:6,codebas:68,narrow:[23,64,68,102,40,112,61,86,83,16],iuml:84,quotient:70,primit:[38,86,102,74,70,20,2,103,68,11,111,32,14,16,115],transit:[32,29,84,48,76,26,12,70,69],establish:[52,74,73,84,48,25,12,70],memor:68,replacedirectcal:32,mylib:65,zeroiniti:70,liber:[25,68],parse_expr:[12,13,14,15,18,19],tackl:[12,15,45,97,48],two:[30,61,0,32,33,1,68,46,3,69,4,70,6,71,37,38,101,84,8,41,5,44,45,2,47,48,10,11,49,12,13,14,15,16,97,18,19,66,52,102,74,54,20,103,76,22,78,80,58,96,23,59,60,83,24,40,86,91,25,88,50,111,107,65,28,29,115],unwindless:30,va_end:70,getbit:20,saptr:70,desir:[30,68,73,1,69,70,6,71,38,5,10,11,49,16,52,74,20,103,76,22,83,88],upper16:22,penultim:52,reconfigur:[26,65,113,52],particular:[30,61,32,33,1,94,68,70,6,71,84,8,101,54,45,46,48,10,73,12,15,16,18,66,52,102,74,20,103,76,21,23,83,29,40,86,88,111,107,26,28],ultrasparc:[23,52],dictat
 :[85,68,16],none:[84,73,1,93,69,4,70,96,12,13,14,15,16,18,19,102,74,20,76,79,80,23,107,61,65,115],dep:[12,13,14,15],elsebb:[39,45,2,47],dev:[77,64,29,9,76,25,80,16],remain:[66,30,68,111,96,74,5,29,45,2,103,10,25,88,93,70,107,14,15,16,115],paragraph:[32,68,105],deb:9,binfmt_misc:23,def:[69,6,64,39,41,54,43,45,2,47,48,12,13,14,15,16,17,18,19,52,103,110,59,84,28,115],mergefunc:30,emiss:[39,52,74,84,45,103,22,88,15,70],sln:35,loopend:[39,15,45,2,47],mcobjectstream:84,minimum:[23,64,68,60,52,112,61,103,25,88,54,70,18],image_file_executable_imag:108,dw_ate_unsign:103,strlen:16,retcc_x86_32_ss:52,calltmp1:[41,13,47,19],calltmp2:[12,48],awkward:[20,68,102],secur:[30,20],programmat:[74,91,8],immutablemap:16,comfort:32,unittestnam:60,cst:70,csv:33,bar_map:68,regener:[61,52,93],our:[84,0,32,68,38,39,8,41,54,43,45,2,47,48,11,73,12,13,14,15,16,17,18,19,20,103,76,23,60,61,62,25,90],"0x0000000000000002":98,number2:32,gcregistri:74,add32mr:6,memory_order_seq_cst:[70,86],associ:[30,68,73,4,70,71,96,
 54,32,16,18,66,52,74,20,103,77,22,78,56,58,59,107,84,88,111,26,115],ccpassbyv:52,sse4:0,binloc:39,sse2:10,mislead:68,cs1:40,image_sym_dtype_arrai:108,rotat:[30,64,84],intermediari:16,isconstantpoolindex:52,mydoctyp:91,through:[30,84,0,32,46,68,4,70,71,39,104,101,40,54,43,97,45,2,47,48,12,13,14,15,16,17,18,52,102,74,20,103,76,21,56,58,60,82,83,77,91,86,25,88,111,27,90],constants_block:111,suffer:74,llvm_src_root:[65,33,50],patfrag:52,late:[73,84,70,52],pch:103,ssl_free:24,clangcommenthtmltag:21,independ:[68,0,4,70,6,37,38,5,97,9,46,11,16,52,102,20,76,56,80,23,24,84,25,88,26,65,27,90,29],pollut:[23,68,87],compound:66,leb128:66,adventur:16,complain:[23,63,8],event:[60,16,88,73],cmpflag:32,mysteri:102,micro:68,token:[91,73,64,39,41,54,43,45,2,47,48,12,13,14,15,17,18,19,24,84,27,28,115],distdir:65,subsystem:[37,84,70],interleav:[70,0],mm5:[6,115],unequ:70,mm7:[6,115],mm6:[6,115],mm1:[6,115],idea:[30,68,31,32,33,34,70,38,41,54,45,2,47,48,11,12,13,14,15,18,19,20,64,103,58,25,111,115],funct
 or:68,mm2:[6,115],image_file_machine_thumb:108,connect:[113,30,59,16,82],orient:[16,38,68,11,101],sparcgenregisterinfo:52,usedlib:[65,50],dw_tag_xxx:103,isref:115,print:[30,91,0,84,33,1,67,35,68,36,70,6,7,39,95,96,40,41,5,97,45,2,47,48,92,12,13,14,15,16,18,19,100,52,53,74,54,20,75,64,103,76,21,89,79,80,57,110,23,106,29,61,87,109,77,112,65,27,114,115],variable_nam:60,dagcombin:64,isinlin:103,cconv:70,mmx:[84,70,52],intregssubregclass:52,suspici:4,b32:8,cuctxdestroi:8,dw_tag_union_typ:103,omit:[30,7,84,95,92,75,47,109,76,77,88,54,36,79,13,57,110,70,18],buildmast:113,testfnptr:70,postdomtre:30,vmov:5,perman:[97,93],clangcommenthtmlnamedcharacterrefer:21,classllvm_1_1dibuild:39,callon:16,registerasmstream:84,printsth:30,exchang:[23,16],argstart:20,done:[30,84,31,32,33,34,93,68,69,4,98,70,71,64,39,96,41,54,45,2,47,48,10,73,12,13,14,15,16,18,19,101,74,90,20,75,103,76,60,83,29,91,85,86,25,107,65,28,115],dylib:[10,62],stabl:[90,25,16,44,93],asmread:64,rootnum:74,functionindex:56,image_sym_t
 ype_uint:108,somewhatspecialsquar:101,expansionregiontag:66,least:[30,68,31,45,1,34,93,70,39,96,40,41,54,9,2,47,48,73,12,13,14,15,16,18,19,52,20,21,78,23,84,86,25,88,111,115],statement:[3,30,64,39,52,0,107,102,45,103,47,21,13,68,15,16,66],createpromotememorytoregisterpass:[39,45],unalign:86,cfe:[23,25,82,93],binop:[39,41,54,45,2,47,48,12,13,14,15,18,19],baseclasslistn:28,selector:[23,52,107,84,103,21,114,70],part:[30,84,32,1,35,68,70,6,38,39,101,40,41,112,43,45,2,47,48,10,11,49,73,12,13,14,15,16,17,18,19,52,102,74,54,20,103,76,21,78,23,60,83,24,91,86,25,111,107,26,65,90,29],pars:[84,73,1,35,69,70,6,71,37,64,39,41,54,43,97,45,2,47,48,12,13,14,15,17,18,19,52,20,103,21,59,90,91,88,111,89,28],toolset:[29,60],contrari:84,cyclic:[23,29],i32:[30,73,3,69,70,6,66,38,8,5,97,45,46,10,11,32,15,16,52,102,74,103,55,78,58,107,29,84,88,105],"_tag":[12,13,14,15,18,19],horizont:5,i8mem:84,"_runtim":88,fpinst:6,constval:16,xxxtargetlow:52,uncontroversi:74,char6:111,debug_loc:89,consol:[12,37,84,105,48
 ],built:[30,84,45,33,93,35,3,70,6,38,39,101,41,54,43,97,9,2,47,48,10,11,12,13,14,15,16,17,18,19,100,52,53,74,20,113,102,23,60,107,29,91,87,63,50,111,26,65],build:[30,68,31,45,33,1,34,67,93,94,35,98,70,6,37,38,39,96,40,41,54,43,97,9,2,47,48,10,11,99,12,13,14,15,16,17,18,19,100,52,53,74,20,75,55,76,113,21,23,60,107,24,84,87,62,63,25,50,111,26,65,90,29,115],extractel:[70,78],distribut:[23,68,98,8,37,33,1,9,87,58,10,35,25,112,65,93,76,6,97],previou:[30,84,31,32,93,68,70,66,64,39,96,8,41,5,97,45,2,47,73,13,14,15,16,18,19,52,76,78,29,91,85,86,111,54,26,105],chart:0,most:[30,61,31,32,33,1,34,93,35,68,36,101,4,70,6,71,37,38,39,84,8,41,5,97,9,2,47,98,10,11,49,45,13,14,15,16,18,19,100,52,102,74,20,75,64,103,76,78,56,23,105,82,73,107,24,40,86,87,62,25,88,50,54,26,65,27,114,28],cygwin:[23,35,84],undetect:24,charg:84,dimension:[14,102,2,8],addsdrr:115,"234000e":[41,19],resolvereloc:71,t2item:32,sector:4,visitbasicblock:16,runonmodul:[76,32],gettypedescript:64,carefulli:[74,25,15,45,103],particul
 arli:[68,52,5,86,76,49,70,16],fine:[68,60,43,29,102,45,17,35,49,78,4,15,16,20],find:[30,91,31,32,33,1,34,93,94,68,4,54,70,6,66,37,64,39,84,40,41,112,44,9,2,47,48,45,12,13,14,15,16,97,18,19,52,102,74,90,20,103,76,23,105,60,83,29,61,63,25,88,50,107,26,65,114,28,24,115],realmag:[14,2],merger:32,filesizepars:20,printmemoperand:52,hasctrldep:[6,115],unus:[30,7,59,8,73,24,84,103,68,26,4,16],express:[30,84,68,70,6,66,7,39,40,41,5,43,97,45,2,47,48,11,12,13,14,15,16,17,18,19,52,102,74,54,20,64,103,23,59,107,24,91,88,38,115],cheaper:16,wrinkl:46,restart:[76,113,24,16],target:[30,84,0,32,33,34,67,93,35,68,69,70,6,71,37,38,39,8,97,9,2,47,48,10,11,49,45,12,13,14,15,100,52,102,74,77,64,103,76,21,22,78,56,80,55,23,60,73,107,29,61,86,87,25,88,111,26,65,27,114,24],misnam:84,mycustomtyp:91,image_file_machine_arm:108,diloc:[29,103],common:[30,91,32,35,68,4,70,6,71,37,38,39,84,8,101,54,97,45,2,47,48,11,49,73,12,13,14,15,16,18,52,102,74,20,99,64,103,76,110,78,96,23,59,107,40,86,87,25,88,50,111,26,65,105
 ,115],intptrsiz:74,clangattrpchwrit:21,"__nv_isnanf":8,printout:[75,16],decompos:[64,25],atomtyp:103,reserv:[52,84,93,88,111,70],mrm1m:52,ccdelegateto:52,someth:[30,91,32,35,68,69,4,70,38,39,84,40,41,5,45,2,47,48,11,12,13,14,15,16,18,19,52,101,20,64,21,110,23,24,61,25,54,105,28,115],someti:70,debat:68,stringifi:103,smallest:[61,70],subscript:[30,70,103,40],experi:[105,60,32,103,34,73,12,65,48],altern:[91,73,33,94,35,70,54,97,45,49,15,16,18,52,102,20,60,107,84,108,83,63,25,90],dw_at_apple_property_gett:103,bourn:[23,20,97],appreci:25,complement:[70,16,102],unrol:[30,70,0],popul:[23,64,8,107,24,1,87,21],alon:[74,54,20,84,10,25,65,18],tempor:70,densemapinfo:16,cpufreq:34,libcrypto:24,simpli:[30,68,73,33,4,70,96,40,41,5,97,9,48,10,12,16,50,19,52,102,20,75,103,76,23,83,84,25,88,18,54,65,27],fldcww:84,point:[91,0,31,32,46,68,101,4,70,6,71,37,64,39,84,8,41,54,43,9,2,47,48,49,45,12,13,14,15,16,17,18,19,52,102,74,20,99,103,76,77,22,80,93,58,23,59,60,73,83,29,40,86,63,88,111,107,113,65,90],in
 stanti:[71,91,101,52,20,1,76,21,16,6,115],alloca:[30,39,102,74,16,84,45,46,103,68,88,49,15,70,85],classof:[21,101],suppli:[23,38,91,70,61,34,87,93,76,90,11,111,107,27,16],setinternallinkag:16,throughout:[71,66,111,23,78,65,4,70],backend:[61,33,70,6,37,64,112,97,46,16,51,100,52,102,74,21,80,23,83,29,84,86,107,114,115],global_begin:[68,16],dovetail:[15,45],aarch64:[23,104,29,87,78,70],"00int":103,linkonce_odr:[70,49,111,8],val1l:70,globalvarnam:70,reformat:27,multiclassobject:28,image_sym_class_extern:108,lto_codegen_add_must_preserve_symbol:90,unnecessarili:[76,40],gap:[68,70],feat_jit:84,understand:[30,84,32,1,35,68,4,70,6,38,39,40,43,97,45,10,11,73,15,17,102,74,99,64,76,82,107,91,25,111,26,65,27,105,28,115],atomicrmw:[70,86],dequ:16,convers:[91,52,8,16,20,0,49,70,115],isstoretostackslot:52,raw:[71,66,7,84,95,106,92,20,75,21,56,27,33],autoregen:52,unifi:[30,38,70,11,49,111,16],fun:[38,43,22,11,65,12,13,14,15,17,19],anonym:[30,68,35,39,41,54,45,2,47,48,12,13,14,15,18,19,52,103,76,25,
 28,115],everyon:[38,25,11,68],subsect:[105,16],propag:[30,59,60,23,70,20,84,107,4,16],lto_codegen_add_modul:90,mystic:[38,11],semispac:74,itself:[91,31,32,1,46,68,70,38,39,84,40,41,112,97,9,2,47,48,10,11,49,45,12,13,14,15,16,18,19,101,53,74,54,20,64,103,76,78,102,23,60,73,90,29,61,87,25,88,111,107,26,65,28,24,115],codegen_func:[12,13,14,15,19],"0x00007ffff7ed40a9":98,case_branch_weight:3,myseqel:91,clangdiagsindexnam:21,incarn:64,benign:33,getlin:39,flag2:32,flag1:32,nameflag:103,"0x3fed":103,sym:[31,110,22],keyt:16,moment:[74,70,86,19],ocamlopt:29,aliassettrack:40,travers:[30,84,101,74,32,1,76,26,16],task:[64,68,74,73,93,107,32,4,16],n_bucket:103,entri:[30,91,32,46,101,4,70,6,71,64,39,84,8,41,5,44,45,2,47,48,12,13,14,15,16,19,52,102,74,103,76,57,58,23,60,107,29,40,88,111,54,26,65,105,115],"16mib":22,parenthes:[68,54,29,1,70,18],uint32_t:[91,103],spend:1,instr_begin:15,ldc:29,obscur:16,ipconstprop:30,ldr:[27,6,78],shape:[93,16,6,101,103],at_decl_lin:103,depriv:16,stwu:84,cut:[20,58,
 52],shiftinst:68,snan:70,singlesourc:[10,33],"0b000000":52,restructuredtext:[23,105,87],objectbodi:28,largeconst:88,realloc:40,rgm:76,bin:[23,31,112,20,9,87,10,63,35,24,6,50],cast_or_nul:16,big:[37,68,52,31,70,29,84,45,2,34,10,41,25,78,80,14,15,16,19],bia:58,judgement:25,transmit:70,ld1:78,bit:[84,31,32,46,3,36,101,70,6,66,38,39,104,96,8,41,5,43,45,2,47,48,11,73,12,13,14,15,16,17,18,19,52,102,74,20,64,103,76,21,22,78,56,23,60,24,91,86,25,88,111,54,113,28,29,115],pcre2:24,knock:68,writealia:32,semi:[26,74,38,11],sema:21,constmerg:30,has_jit:26,aliasset:[52,40],often:[30,61,91,84,68,70,37,38,101,8,5,97,45,48,10,11,49,12,15,16,18,52,102,74,20,64,103,78,23,60,83,40,86,25,54,65,115],steensgaard:40,weakodrlinkag:16,dllimport:[70,111],back:[84,45,93,94,68,70,6,37,39,96,8,41,97,9,2,47,48,10,72,73,12,13,15,16,102,99,103,21,23,60,83,91,85,62,25,88,107],bach:4,"0x00002000":103,breviti:[78,8],densemap:16,sizeof:[38,8,70,97,11,16],sparcreg:52,cmpgep:32,scale:[68,101,102,74,84,21,58],arcmt:34,per
 :[91,33,36,70,66,96,8,48,12,16,101,74,20,103,76,21,58,60,90,29,84,86,110,88,111,107,26,65,28,24],usernam:[23,25],substitut:[30,84,74,1,86,10,88,5,115],mathemat:[8,32,97,54,70,18],larg:[30,68,33,93,35,36,69,70,6,8,112,46,48,10,49,12,16,50,52,20,103,22,80,23,83,24,84,86,25,88,111,65,29],reproduc:[24,61,45,10,25,15,83],createentryblockalloca:[39,45],bb0_1:8,intial:16,patient:76,c0c0c0:84,initialse:42,addpdrr:115,unvectoriz:0,llvm_definit:60,adc64rm:6,addpdrm:115,float_of_str:[12,13,14,15,17,18,19],deadtypeelim:[30,16],bugpoint:[23,7,37,112,61,67,76,35,25,30,83],impos:[70,25,16,84,88],usb:34,constraint:[30,64,84,52,16,75,76,70,6],preclud:[73,78],createfadd:[39,41,45,2,47,48],litconfig:1,forexprast:[39,45,2,47],disclosur:25,timberwolfmc:33,fmin:70,add32mi8:6,keystrok:68,nsz:70,frames:74,"_build":[23,87],nsw:[25,70,49,102],inclus:[52,65,4,114,70,50,115],errno:[70,40],megabyt:[23,87,112],x86_fastcallcc:111,subst:[28,6,115],includ:[30,84,107,0,45,33,1,68,46,94,35,3,36,69,4,54,70,6,71,37,38,
 39,104,96,8,41,5,43,97,9,2,47,48,10,11,73,12,13,14,15,16,17,18,66,100,52,101,74,90,20,75,64,103,76,21,78,102,93,23,60,82,106,83,24,40,86,87,63,25,88,50,112,26,65,27,114,28,29,115],cptmp0:52,cptmp1:52,forward:[30,68,4,70,64,40,41,54,43,47,16,17,18,19,103,56,107,29,84,111,28,115],image_scn_align_1byt:108,llvm_build_doc:60,tinyptrvector:16,reorgan:91,dwarfdump:[89,103,67],int8_t:91,translat:[66,23,38,39,95,52,30,70,20,40,68,103,91,21,11,86,102,84,16,97,114],llvmfoldingbuild:12,sdk:35,concaten:[28,23,16,103,10,78,70,115],internaltarget:65,mfenc:86,exported_symbol_fil:65,movsx16rr8w:84,dw_tag_const:103,movnt:70,v8i16:52,curr:17,xxxiter:16,attrinfomap:21,flow:[30,91,0,73,68,70,71,38,39,84,8,41,54,43,44,45,2,47,48,11,12,13,14,15,16,17,18,19,51,52,76,83,29,40,25,107,105,90],debug_nam:103,clangattrlist:21,"__vectorcal":29,isdigit:[39,41,54,43,45,2,47,48],prevail:96,singli:74,cmake:[23,60,113,37,24,53,9,87,76,63,35,26,105,29],crypt:25,sequenti:[5,84,107,111,70,16],declas:70,llvm_target_arch:6
 0,vg_leak:1,asymmetr:102,deseri:21,llvm:[0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26,27,29,30,31,32,33,34,35,36,37,38,39,40,41,42,43,44,45,46,47,48,49,50,51,52,53,54,55,56,57,58,59,60,61,62,63,64,65,66,67,68,70,71,73,74,75,76,77,78,79,80,82,83,84,85,86,87,88,89,90,91,92,93,94,95,96,97,98,100,101,102,103,105,106,107,109,110,111,112,113,114,115],functionnod:32,mismatch:[39,109,41,97,45,2,47,48,78,12,13,14,15,70,27,19],globalvar:111,tok_numb:[39,41,54,43,45,2,47,48],cater:21,extrahelp:20,deserv:49,image_sym_type_float:108,image_comdat_select_associ:70,downcast:101,i16:[84,70,52,8],tradeoff:[12,74,86,48],required_librari:26,type_code_float:111,dwarfregnum:52,"0fb5bfbe8e":8,addescapingus:40,queri:[30,38,84,52,0,70,20,40,103,86,76,68,11,49,56,69,16],mantain:93,strex:86,regallocregistri:76,demangl:[79,110,103],privat:[68,101,52,8,16,103,113,21,25,49,111,32,26,70],antisymmetr:32,sensit:[76,91,44,60,40],elsewher:[65,52],createtargetasminfo:52,granular:4,cumoduleloa
 ddata:8,exit:[30,68,32,33,1,5,94,36,98,70,7,39,95,96,8,112,44,45,2,47,48,11,49,42,92,13,16,97,100,53,74,75,38,76,77,79,80,57,58,106,107,24,84,109,110,89,114],"6666ff":84,priority_queu:16,immsubreg:52,vla:[22,102],named_valu:[12,13,14,15,19],cudeviceptr:8,volum:[37,16,103,65],implicitli:[84,0,68,70,38,41,54,43,2,47,48,11,12,13,14,15,16,17,18,19,20,76,29,91,25,88,111,65,28,115],postord:59,refer:[30,91,31,32,1,93,68,70,6,71,37,39,104,84,8,41,5,97,45,47,10,73,13,15,16,18,19,66,52,102,74,54,20,103,76,21,22,78,56,80,110,58,23,59,60,82,83,29,40,107,88,111,112,26,65,27,28,115],pbqp:[84,77],fortun:[38,68,45,47,48,11,12,13,15,16],veli:84,dw_virtuality__virtu:103,"0x3":[88,16],"0x2":[88,16],"0x1":[88,16,103],"0x0":[16,111],toplevelexpr:[39,41,54,45,2,47,48,12,13,14,15,18,19],"0x5":88,"0x4":88,append:[60,96,70,95,103,10,94,111,112,13,16,50,115],"0x1f84":79,resembl:102,unwound:70,access:[30,91,0,32,94,35,68,70,71,38,84,8,102,45,11,15,16,52,53,74,20,64,103,76,21,78,110,96,23,29,40,86,25,88,113,11
 5],agg1:70,microprocessor:[84,70,52],regstat:84,deduc:[28,115,70,49,30],camlp4:[17,18],sint:70,"0xk":70,objects:70,partialalia:40,"0xm":70,jonathan2251:51,"0xc":111,getsourc:23,sine:[70,52],sinc:[61,91,31,32,34,93,35,68,69,4,70,6,71,39,84,8,41,54,43,97,9,2,47,48,45,12,13,14,15,16,18,19,52,102,74,101,20,103,76,58,96,23,73,107,29,40,85,25,88,111,65,105,28,24],"0xe":111,"0xd":111,remark:[83,0],fpregsregclass:52,cerr:8,implement:[30,91,31,32,1,77,46,68,101,4,98,70,71,37,38,39,84,8,41,54,43,102,45,2,47,48,11,73,12,13,14,15,16,17,18,19,51,52,53,74,20,64,103,76,21,22,78,58,96,23,59,90,24,40,85,86,63,25,88,107,26,65,27,28,29],foundat:76,domtre:30,mov64ri:52,tool_nam:23,expr1lh:66,toshio:84,getimm:52,websit:[61,93],advoc:68,projlibspath:65,select_isd_stor:52,"_regoffset":6,acc:16,at_encod:103,int32ti:16,trait:[68,91,16],attrspel:21,image_scn_align_512byt:108,trail:[66,91,102,16,20,1,103,68,70],train:29,iii:29,account:[23,101,82,74,32,25,113],dcmake_c_compil:24,komatsu:84,alia:[30,59,52,0,32,
 20,40,46,86,76,110,37,111,102,84,70,29],createlocalvari:39,rdynam:[14,15,2,48],obvious:[30,64,84,102,40,31,16,20,43,68,76,25,54,32,70,17,18,115],ch8:39,unread:[68,86],fetch:[23,3,70,84],aliv:[76,30,84,16,32],n2657:68,abcd:111,tarbal:[37,93,9,65],onlin:[15,45],formmask:52,serial:[64,32,29,91,21,65,50],everywher:[10,12,91,48,32],surfac:84,rootcount:74,optyp:52,add32rm:6,inteldialect:70,gcn:72,ssl_ctx_use_privatekey_fil:24,usub:70,smovq:84,add64mr:6,powerpc64:104,getehframesect:71,inst:[30,24,16,52,115],nothidden:20,llvm_include_dir:60,redund:[30,59,20,84,48,12,16],philosophi:[26,37,90,83,103],physic:[73,84,16,52,115],bind:[68,70,37,39,41,54,97,45,2,47,48,12,13,14,15,18,19,52,29,91,28,115],correspond:[30,91,32,35,68,69,5,6,66,64,39,101,8,41,70,44,47,13,84,16,97,18,19,100,52,102,74,54,20,103,55,76,77,22,78,79,23,59,60,83,61,86,87,25,111,107,28],afterloop:[39,45,2,47,13,14,15],region1:66,region0:66,noitin:80,fallback:111,loopendbb:[39,45,2,47],writethunkoralia:32,c11b17:84,ptr_rc:84,symb
 olt:16,cpu_x86_64:91,cflag:[65,50],bunch:[43,33,97,2,48,12,14,16,17],acycl:[84,59,52,114],outputdebuginfo:20,labor:20,i1942652:70,typemap:64,immtyp:6,dag:[59,52,28,84,5,58,10,21,114,16,6,115],uncategor:20,passnam:75,dan:91,spell:[21,68],dai:[37,38,60,23,93,25,11,16],symbol2:22,symbol1:22,nval:70,mylist:91,isimplicitdef:6,strive:[10,68],createfcmpult:[39,41,45,2,47,48],parseexpress:[39,41,54,45,2,47,48],mem2reg:[74,30,15,16,45],destarchivelib:65,sin:[91,0,41,54,43,40,48,12,70,17,18,19],dllvm_libdir_suffix:60,machinebasicblock:[84,16,52],add16ri8:6,lie:20,postdomfronti:30,intellig:[70,16],cmake_module_path:60,addtypenam:16,llvmbug:37,llvmsupport:[65,50],fluctuat:40,function_ref:16,paramattr:111,twice:[23,31,32,48,76,35,12,65,70,16],createmyregisteralloc:76,rev:[78,12,13,14,15,18,19],ret:[30,70,8,41,5,97,45,47,48,10,12,13,15,16,19,102,74,103,55,78,29,84,85,88,105,115],stub:[32,84,16,104,52],typenam:[64,16],stuf:5,rel:[68,31,33,1,93,36,70,37,39,5,97,47,13,16,50,74,20,22,58,23,24,84,85,8
 8,111,27],rem:84,image_file_machine_powerpc:108,rec:[12,13,14,15,17,18,19],dw_apple_property_assign:103,barrier0:8,ref:[23,30,8,41,54,40,45,2,47,48,76,39,12,13,14,15,115,18,19],reg:[52,8,84,88,27,5,115],math:[68,8,20,0,43,2,103,77,49,80,14,70,17],clarifi:[103,86],insid:[30,84,31,32,33,1,68,70,66,37,9,98,10,16,101,53,74,103,76,21,23,24,91,87,111,28,115],workflow:24,flaghollow:91,attrbuild:56,standalon:[26,84,39,49],releas:[68,31,73,93,70,37,41,97,16,50,100,52,76,56,23,60,24,84,86,87,62,63,25,88,65,90,29],bleed:37,indent:[39,68,105,91],retain:[59,16,20,97,103,76,25,78,65,70],hex64:91,suffix:[76,64,68,60,96,52,41,16,20,1,10,94,95,77,92,65,70,19],createcompileunit:39,pgo:109,targetregsterinfo:84,pgr:37,ualpha:28,secondlastinst:52,facil:[68,40,74,20,1,103,35,65,4,29,50,97],suffic:78,llvm_enable_eh:60,target_data:[12,13,14,15],messag:[96,23,25,60,106,33,37,107,83,20,1,68,91,76,21,29,59,82,5,6,61],dw_apple_property_sett:103,llvmusedlib:65,comparefp:115,debuginfo:[10,30,39,103],ogt:70,mytoo
 l:65,s32:8,pg0:32,pg1:32,"__objc_imageinfo":70,xarch:23,image_file_aggressive_ws_trim:108,source_i386:79,prune:30,rpass:0,structur:[30,84,0,32,33,67,35,68,70,6,71,38,39,96,40,41,5,43,44,45,2,47,48,10,11,49,12,13,14,15,16,17,18,19,66,52,53,74,54,20,103,76,21,56,102,59,83,29,91,86,111,107,26,65,105,90],charact:[1,94,70,66,39,96,41,5,43,45,2,47,48,10,12,13,14,15,16,17,18,19,20,103,21,84,110,111,54,65,27,28,115],"123mb":20,then_val:[13,14,15],"4a789c":66,plaintext:[23,87],thereaft:88,subclassoptionaldata:32,deprec:[60,52,29,10,111,16,33],ispack:111,have:[1,2,4,5,6,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26,27,28,29,30,31,32,33,34,35,36,37,38,39,40,41,54,43,44,45,46,47,48,49,50,66,52,103,56,58,60,61,63,65,68,69,70,71,73,74,75,76,110,78,83,84,85,86,87,88,91,93,94,96,97,99,101,102,64,82,107,111,113,105,115],tidi:76,eatomtypedieoffset:103,min:[31,70],mib:22,mid:[70,46],in64bitmod:84,sspreq:[70,111],mix:[68,102,0,5,84,63,90,26,16],builtin:[23,39,8,20,1,45,2,53,86,76,111,14,15,70,
 18],startval:[39,45,2,47],p3i8:8,mit:25,analysi:[30,0,33,36,69,70,66,37,64,39,40,97,45,2,47,48,49,12,15,102,74,75,103,76,58,23,59,60,90,84,86,28],poison_yet_again:70,unless:[30,68,33,93,70,7,5,97,45,47,10,72,49,13,15,16,52,102,20,76,77,23,60,106,83,24,87,25,88,107,65,105],preliminari:[30,52],eight:[84,70,96],transcript:[12,48],memorydependenceanalysi:40,v8i32:70,arm_aapcs_vfpcc:111,gather:[0,32,20,10,21,25,107,26,16,50],hardcod:[69,52],image_file_machine_mipsfpu16:108,getdirectori:[39,103],institer:16,instantiatetemplateattribut:21,occasion:[74,111],addpassestoemitmc:71,addtmp:[39,41,45,2,47,48,12,13,14,15,19],dllexport:[70,111],ifconvers:52,text:[68,32,33,5,38,96,43,10,11,17,52,20,64,110,22,60,82,24,84,108,25,88,65,27,105,28],ifconvert:52,sanitize_thread:70,llvm_map_components_to_libnam:60,setter:[21,16,103],dw_tag_pointer_typ:103,loweroper:52,categor:[30,20,21,52],src_root:[23,87],"__morestack":85,cpunam:[80,77],inferior:98,data64bitsdirect:52,print_newlin:[12,13,14,15],lower_boun
 d:16,litvalu:111,sysv:110,disagre:70,bear:5,dllvm_dir:60,image_sym_class_member_of_struct:108,increas:[30,68,0,41,61,25,49,99,80,90,6,19],gcwrite:[74,70],at_end:[12,13,14,15,19],callpcrel32:115,blogspot:24,integr:[30,97,60,51,74,90,20,1,53,76,67,26,70,29],printlabel:52,conform:[23,1,74,16,91,68,70,97],project_nam:50,emitfnstart:84,ssl_ctx:24,dw_tag_file_typ:103,reform:68,pattern:[68,67,5,6,64,8,41,70,43,10,16,17,18,52,102,20,103,21,78,29,84,86,65,115],boundari:[30,78,84,103,111,70],uninlin:70,callgraphsccpass:76,progress:[59,60,43,1,93,25,72,104,84,16,17],"0b100":115,"0b101":115,vadv:33,switchtosect:84,resolvecycl:29,nvptx64:8,phase3:31,plugin:[37,74,112,29,75,63,80],equal:[68,32,3,70,39,52,40,54,97,45,2,47,13,14,15,16,18,101,20,58,107,84,111,115],instanc:[84,31,32,1,93,68,70,71,37,38,101,41,5,46,10,11,16,18,19,52,74,20,103,76,21,60,82,91,88,54,115],valuelistn:28,comment:[30,84,32,68,70,6,38,39,41,5,43,45,2,47,48,10,11,12,13,14,15,16,17,18,19,101,53,74,21,82,29,91,25,54,26,65,28,115
 ],revert:[23,25],guidelin:[16,68,9,105],vend:46,unreferenc:[65,70],inoperandlist:[6,52],defini:69,llvm_cmake_dir:60,type_info:107,autovector:0,component_1:26,component_0:26,createmul:16,assert:[30,68,91,31,34,93,39,8,97,45,2,84,16,52,20,76,23,60,29,61,87,62,65,24],determinist:[83,21,16,84,40],multi:[37,68,16,20,57,90,29],plain:[74,76,105,16],defin:[30,61,107,91,32,33,1,46,68,36,69,4,70,6,66,37,38,39,84,8,41,5,43,97,9,2,47,48,10,11,49,45,12,13,14,15,16,17,18,19,51,52,53,74,54,20,64,103,76,21,22,78,102,93,58,96,23,60,73,90,29,40,86,62,55,25,88,50,111,112,26,65,105,28,110,115],deem:[64,61,70,93],operandtyp:52,noimplicitfloat:[70,111],func_typ:73,helper:[68,32,1,71,39,40,41,54,45,2,47,48,10,14,15,16,17,18,19,52,20,103,21],almost:[23,64,59,74,29,84,68,78,4,16],irreduc:[30,52],maystor:6,isreturn:[6,115],build_alloca:15,substanti:[12,68,48,70,40],prose:68,unneed:[15,45],dw_op_piec:103,llvm_enable_zlib:60,japanes:23,whenev:[68,40,5,20,98,10,69,88,70,112,26,65,16,43],codepath:86,infer:[84,10
 1,53,91,68,77,49,78,80,65],backtrac:[84,39],clangdiaggroup:21,denot:[23,84,74,91,111,70],valueopt:20,dealloc:[74,70,16],default_branch_weight:3,sm_30:84,image_scn_align_32byt:108,sm_35:84,mcsection:84,center:[84,39],neural:33,nevertheless:70,getopcod:[16,52],builder:[23,39,37,41,54,45,2,47,48,113,56,12,13,14,15,16,18,19],dfpregsregisterclass:52,setp:8,choos:[84,69,70,41,112,43,47,48,12,13,16,17,18,19,52,20,103,76,78,80,60,61,25,54,113,65],setvector:16,usual:[68,32,33,36,70,38,39,101,40,5,10,11,16,52,102,74,20,75,64,103,76,22,23,59,60,83,29,84,85,86,63,25,111,65,105,90,24,115],unari:[38,39,43,45,2,11,14,15,28,17],tarjan:76,getgloballist:16,findcustomsafepoint:29,listconcat:[28,115],numberexprast:[39,41,54,45,2,47,48],p18:8,settabl:65,p19:8,tough:[54,18],cortex:[9,34,56],gendfapacket:84,adt:[23,39,16,60],tight:[90,49],add_cfg_simplif:[12,13,14,15],onward:60,uwtabl:[70,103],add:[30,61,107,91,31,32,33,1,94,68,54,69,4,98,70,6,37,38,39,84,8,41,5,43,97,9,2,47,48,10,11,49,45,12,13,14,15,16,
 17,18,19,52,102,74,101,20,75,64,103,76,56,96,23,60,82,83,29,40,86,62,25,88,50,111,112,113,65,115,28,99],cleanup:[30,59,107,103,46,47,48,25,12,13,70],adc:[30,59,16,40],voila:24,citizen:16,dced:16,c11:86,successor:[30,84,52,16,44,68,49,70,58],match:[30,84,73,33,1,67,68,70,66,7,101,41,5,43,44,48,10,12,13,14,15,16,17,18,19,52,102,74,20,64,103,76,21,23,83,29,91,86,107,111,112,26,65,90,115],apple_typ:103,llvmsharp:29,hypersparc:52,fnscopemap:39,pcre2posix:24,image_file_net_run_from_swap:108,punctuat:[68,28],realiz:[12,14,48,2,64],llvalu:[12,13,14,15,19],coldcc:[70,111],module_code_purgev:111,insert:[30,68,32,4,70,39,96,40,41,45,2,47,48,73,12,13,14,15,16,19,52,74,20,103,76,78,83,29,84,86],like:[30,91,31,32,33,68,34,35,3,101,4,70,6,97,71,38,39,84,8,41,5,43,44,9,2,47,48,10,11,49,45,12,13,14,15,16,17,18,19,66,52,102,90,20,64,103,76,110,96,23,60,82,73,83,24,40,85,86,87,62,25,88,111,54,26,65,27,105,28,29,115],studi:50,sstream:68,registeranalysisgroup:[76,40],inferenc:84,c1x:70,soft:[4,103,80],c
 rawler:74,unreach:[66,30,7,39,74,32,97,45,2,47,48,49,12,13,14,15,70],convei:[107,70,49],registermcobjectstream:84,proper:[66,68,101,52,16,1,86,70],getparamtyp:16,release_1:23,tmp:[102,74,70,84,45,103,48,10,79,12,15,5,50,16],nvcc:84,add_instruction_combin:[12,13,14,15],llvmrock:68,esp:[84,5,6],nvcl:8,"__internal_accurate_powf":8,dw_tag_structure_typ:103,intregsregisterclass:52,dce:[30,20,64,112],noisi:[30,25,16],host:[71,23,39,60,8,74,70,24,84,9,34,87,10,68,37,65,16,29,97],"0xffff":88,clangattrtemplateinstanti:21,geometr:[38,11],simpler:[30,64,29,84,45,2,103,14,15,70],about:[30,61,0,31,32,33,1,77,34,93,35,68,36,69,4,98,70,71,37,38,39,84,8,41,5,43,97,9,2,47,48,11,49,45,12,13,14,15,16,17,18,19,52,102,74,101,20,99,64,103,76,21,57,110,58,96,23,60,82,106,73,90,24,40,86,87,109,62,25,88,54,111,107,113,65,27,105,28,29,115],actual:[30,84,31,32,33,1,68,101,4,70,71,38,39,96,40,41,5,43,97,45,2,47,48,10,11,49,73,12,13,14,15,16,17,18,19,52,102,54,20,103,76,113,78,23,59,83,24,91,25,88,50,111,107,26
 ,65,115],endcod:68,madechang:74,discard:[70,20,84,22,23],addendum:37,upward:1,abical:29,guard:[68,70,21,22,49,65,16],been:[30,84,107,31,32,1,93,68,36,4,98,70,6,71,38,96,8,41,5,97,2,47,48,11,99,73,12,13,14,16,18,19,52,102,74,54,20,75,64,103,76,78,23,82,83,29,91,86,87,25,88,50,112,65,105,28,115],ifexpr:[39,45,2,47,13,14,15],rcx:6,eh_fram:107,naveen:30,rcn:31,getelementptrinst:16,biggest:[84,46],calltwo:16,log10:[70,0],functionlisttyp:16,unexpect:[68,32,33,45,35,25,15],f4rc:84,bur:59,brand:76,machinefunctionpass:[76,52],bui:34,uninstal:65,inlin:[30,84,68,70,38,8,43,97,47,48,11,12,13,16,20,75,103,76,79,23,82,107,29,91,25,88],bug:[84,31,32,33,5,93,68,70,6,37,7,45,41,112,44,9,10,11,73,15,16,97,19,101,38,110,23,83,24,61,25,28,29,115],wise:70,mcpu:[52,8,9,10,77,80],wish:[23,64,61,60,52,102,32,20,1,87,93,49,73,65,16,115],srcarglist:70,rc1:[31,93],install_prefix:60,virtregmap:84,emitjumptableinfo:52,pin:70,hashfunctiontyp:103,dure:[84,0,31,32,33,93,69,70,37,64,41,10,73,16,19,52,74,20,103,58,2
 3,107,29,91,87,25,88,90],pic:[84,52,29,61,9,80],int64_t:[91,16],probabl:[38,84,102,16,20,65,68,34,47,94,25,11,50,36,13,54,70,58,18,97],llvm_append_vc_rev:60,guidanc:[68,49],detail:[30,91,0,32,93,35,68,36,4,70,37,38,84,40,41,43,97,45,2,10,11,14,15,16,17,50,19,52,102,20,103,76,113,21,58,96,23,59,60,83,24,61,85,86,87,109,25,107,26,65,27,90,29],virtual:[30,68,1,4,5,6,39,101,40,41,54,97,45,2,47,48,99,15,16,19,100,52,74,103,76,21,56,84],dw_apple_property_strong:103,out:[30,91,31,32,33,1,34,93,35,68,36,69,4,70,6,38,39,84,40,41,54,43,102,9,2,47,48,10,11,45,12,13,14,15,16,17,18,19,52,53,74,20,99,64,103,76,21,78,79,80,55,96,23,60,73,83,24,61,86,87,63,25,111,107,65,29,115],result_int:73,apple_objc:103,gcc:[30,61,0,33,93,94,68,70,37,104,112,97,9,16,52,20,103,23,107,29,84,86,87,63,65],pi8:55,winzip:35,ksdbginfo:39,al_aliasset:52,customroot:74,afterbb:[39,45,2,47],binoprh:[39,41,54,45,2,47,48,12,13,14,15,18,19],predsens:69,unshadow:[39,45,2,47,13,14,15],vliw:[84,21,114],twoaddressinstructionpass:
 84,eliminateframeindex:52,liveout:[73,88],poorli:[29,68,58],getreginfo:84,undef:[5,97,46,86,21,70,107,16],patcher:88,isvi:52,spec:[28,91,16,33,61,103,93,10,70,115],add_incom:[13,14],concret:[101,52,73,20,84,48,76,111,12,93,16,6,115],under:[68,73,1,70,6,66,38,8,112,97,46,10,11,18,51,52,20,76,113,23,60,29,84,87,63,25,54,26,65],runhelp:68,playground:[43,17],everi:[30,84,31,32,33,1,68,34,93,94,3,4,70,6,66,37,38,39,8,54,97,45,47,48,10,11,73,12,13,15,16,101,74,20,75,103,76,78,58,23,59,83,24,40,85,86,87,109,25,88,111,26,65,115],risk:[70,93],f934:52,rise:68,risc:[86,52],implicit:[68,52,70,24,84,47,21,13,115,5,16],clangattrclass:21,capturestackbacktrac:29,upstream:23,printfunctionpass:30,read_regist:70,llvm_yaml_strong_typedef:91,mygc:74,isv9:52,isdefinit:103,x86_64:[23,84,31,70,29,91,9,34,87,10,49,79,5],zlib:[23,60],x86call:115,xxxinstrinfo:[69,52],naiv:30,request:[71,96,82,74,70,25,88,111,107,90,115],nail:[13,47],xor32rr:84,llvm_yaml_is_document_list_vector:91,llvmtransformutil:50,blockinf
 o:111,hide:[20,68],introspect:[27,90,56],foundfoo:68,poison:70,hi16:84,conduct:25,postdomin:30,asymmetri:32,functiontyp:[39,41,45,2,47,48,16],studio:[23,68,60,37,35,22],debugg:[71,23,38,39,30,76,37,84,103,47,83,10,68,11,107,13,110,98,70],path:[30,68,9,33,1,94,35,70,96,8,112,97,45,10,49,73,15,16,50,100,53,74,103,76,77,79,80,23,60,107,24,40,86,87,63,65,114,29],dlopen:[76,65],forum:[37,70],typebuild:16,mypassopt:76,anymor:[76,29,16],pointcount:74,precis:[23,84,101,52,30,41,54,29,40,43,103,86,77,88,80,70,17,18,19],portabl:[37,38,84,74,16,29,1,68,11,65,4,70,97],nontempl:20,bitset2:55,distalwai:65,printd:[38,39,45,2,11,14,15],strai:10,printf:[66,23,39,83,97,45,2,103,63,35,90,14,15,70],cont:[70,46],ymin:[14,2],smallsetvector:16,describ:[30,91,32,33,1,67,93,68,69,70,6,71,37,38,39,96,8,41,54,43,102,2,47,48,11,49,73,12,13,14,84,16,17,18,19,66,52,53,74,101,20,64,103,76,77,22,78,58,23,107,29,61,25,88,50,111,26,65,90,115],would:[30,91,0,32,93,35,68,36,4,70,6,66,38,39,40,41,5,97,77,2,47,48,10,11,
 49,73,12,13,14,84,16,18,19,101,102,74,20,103,76,113,21,78,58,23,59,107,29,61,86,63,25,88,50,111,54,26,65,105,28],gcstrategi:[74,29],addincom:[39,45,2,47],llvm_doxygen_qhp_cust_filter_nam:60,autogen:24,n1720:68,must:[30,61,91,32,33,1,46,94,68,101,4,70,6,71,64,39,84,8,41,5,97,9,2,47,10,45,13,14,15,16,50,19,52,102,74,20,103,55,76,22,78,93,96,23,59,60,73,90,29,40,86,87,25,88,111,107,26,65,105,28,115],shoot:[12,48],join:[76,70,16,80],getnumoperand:16,"0x4db504":24,image_file_machine_mipsfpu:108,runfunct:[16,98],targetframelow:84,introduc:[30,73,46,70,6,52,40,5,45,2,47,32,13,14,15,101,93,29,84,86,88,115],overrid:[30,68,92,94,70,39,52,40,32,16,101,20,76,77,80,23,84,86,87,21,65,28,115],"__data":70,virtreg2indexfunctor:84,inadvis:102,registerehfram:71,dw_tag_label:103,attract:[74,25],makellvm:23,enc:103,end:[72,30,61,0,31,32,33,93,68,101,4,54,70,6,97,66,37,38,39,95,84,8,41,5,43,44,9,2,47,48,10,11,49,45,12,13,14,15,16,17,18,19,52,102,74,90,20,99,103,76,21,22,78,96,23,60,82,83,77,40,87,91,25,8
 8,50,111,107,65,105,28,115],straightforward:[38,101,52,41,103,97,45,2,47,48,76,11,78,12,13,14,15,16,19],pipefail:1,concis:[20,84,68,102],hasnam:16,env:31,frameless:84,ancestor:[70,101],collaps:70,dialect:[27,70],memorydependencyanalysi:86,createfil:39,attrdoc:21,badli:49,getreservedreg:52,attrspellinglistindex:21,parallel:[23,59,60,0,24,1,87,62,113,65,84,70,29,50],bootstrap:23,r_arm_thm_movw_abs_nc:9,parserclass:20,includedir:[65,100],environ:[76,23,84,60,94,30,74,70,20,1,86,87,62,63,68,22,65,4,16,29,97],reloc:[71,84,52,73,29,61,9,22,80,57,70],enter:[23,84,82,107,1,103,87,48,111,54,12,83,18],exclus:[73,20,70,86],composit:[16,103],over:[30,68,70,38,39,40,41,43,97,45,2,47,11,49,13,14,15,16,17,19,101,102,74,90,78,59,82,83,84,111,28,115],commasepar:20,imul:84,blatent:[15,45],optional_dir:[65,50],str_offset:103,rfunc:7,parseparenexpr:[39,41,54,45,2,47,48],align32bit:111,imm:[27,84,52,115],baseinstrinfo:21,image_sym_type_dword:108,tramp:70,replaceinstwithinst:16,getorinsertfunct:16,llvmbi
 tread:50,comprehens:[10,23,29,30],llvmbc:[29,111],settruncstoreact:52,cfgsimplifi:16,getlazyresolverfunct:52,echo:[23,105,65],const_global_iter:16,"0x60500020":108,alex:66,exampletest:1,modrefresult:40,each:[30,61,91,31,32,33,1,77,93,94,68,69,4,54,70,6,71,37,64,39,84,8,41,5,43,97,45,2,47,48,10,73,12,13,14,15,16,17,18,19,66,100,52,101,74,90,20,75,103,55,76,21,78,56,80,57,110,58,96,23,102,60,106,83,24,40,86,87,62,25,88,50,111,107,26,65,28,115],use_begin:[68,16],sk_lastsquar:101,prohibit:[90,86],abbrevwidth:111,runtest:[31,9],ptrtoreplacedint:16,tag_pointer_typ:103,goe:[39,60,84,52,8,74,16,24,61,45,103,91,107,86,65,27,15,70,29,97],newli:[30,39,41,73,2,47,48,63,12,13,14,16,19],laid:[16,84,48,78,12,70],adjust:[52,32,97,45,46,10,88,15,70],has_disassembl:26,got:[23,39,20,61,48,12,84,16],frem:70,debug_pubnam:103,precaut:16,threadidx:8,free:[68,73,93,38,104,40,41,43,48,10,11,12,16,17,19,74,76,59,82,29,84,86,65],getfilenam:[39,103],rangelist:28,galina:113,precompil:8,distract:25,puzzl:61,astd
 ump:21,r9d:6,r9b:6,openssl:24,filter:[60,107,84,10,69,70],addrspac:[73,70,8],rais:[30,74,70,83,107,12,13,14,15,16,17,18,19],runtimedyldimpl:71,r9w:6,onto:[23,74,32,84,103,93,25,70,16],rang:[68,0,70,66,37,39,40,43,2,48,72,49,12,14,16,17,101,102,74,20,103,76,77,22,58,83,84,107,115],neededsafepoint:74,xnorrr:52,wordsiz:74,rank:30,restrict:[68,0,73,70,64,97,46,99,16,102,74,20,103,76,22,107,24,84,86,25,88,28],datastructur:16,alreadi:[91,32,46,68,101,70,6,64,39,84,40,41,43,97,45,2,47,48,10,12,13,14,15,16,17,50,19,52,74,20,103,76,23,60,29,61,85,25,88,105,24],hackabl:[43,17],createcfgsimplificationpass:[39,45,2,47,48],primari:[70,37,39,40,41,54,43,45,2,47,48,12,13,14,15,16,17,18,19,74,29,84,25],rewritten:[29,84],exp2:[70,0],top:[30,84,32,33,1,46,68,70,38,39,40,41,5,97,45,2,47,48,10,11,12,13,14,15,16,18,19,102,53,20,103,76,21,80,23,60,82,107,29,91,63,25,50,111,54,26,65,28],seq_cst:[70,86],downsid:16,tok:39,toi:[38,39,43,41,54,24,45,2,47,48,11,12,13,14,15,17,18,19],ton:[43,17],too:[84,32,34,3
 5,68,4,70,38,39,54,45,10,11,15,16,18,20,76,23,83,29,91,63,25,65,24,115],tom:91,toc:[84,88],initialize_native_target:[12,13,14,15],createalloca:[39,45],quiet2:20,tool:[30,61,31,1,67,94,35,68,36,4,98,70,6,97,66,37,7,104,8,41,5,43,44,47,48,10,42,12,13,84,16,17,50,19,100,52,53,74,20,103,76,22,57,23,59,60,82,83,29,40,87,109,62,63,25,111,112,26,65,90],usesmetadata:74,took:[39,41,45,2,47,48,12,13,14,15,19],targetgroup:26,conserv:[68,40,74,73,86,93,76,90,88,70,58],removeus:32,reinterpret_cast:24,ashr:70,expr:[7,39,54,45,2,47,114,12,13,14,15,18,19],zero:[30,68,0,92,1,5,94,36,70,71,7,95,8,112,44,47,10,11,49,13,14,15,16,18,66,100,52,53,74,20,75,38,103,77,78,80,102,106,107,29,84,110,88,111,54,114,115],fashion:[70,64,22,52,23],ran:[76,94],ram:113,dw_tag_string_typ:103,lbd:51,further:[111,23,68,60,107,52,102,74,5,24,103,87,35,25,70,32,65,16,29,50],unreloc:73,rax:[88,6,52],adc32mi:6,unresolv:[65,38,1,11,29],thorough:68,sk_somewhatspecialsquar:101,xfail:[10,33,1],contact:[76,113,29,25],expr0lh:66,t
 horoughli:[13,47],adc32mr:6,atom_count0:103,though:[30,68,32,33,70,64,39,41,54,45,47,10,12,15,16,18,19,101,102,74,20,103,76,58,107,84,86,90],visitfab:64,glob:7,"__apple_typ":103,bss:80,sethi:52,bsd:[23,110,25,96,65],"0x00000002":103,"0x00000003":103,"0x00000000":103,"0x00000004":103,"0x00000009":103,metal:70,roots_begin:74,getorcreatefoo:16,abbrev:[89,111],declar:[30,84,32,46,68,4,70,6,64,39,101,8,41,5,43,97,45,2,47,48,73,12,13,14,15,16,17,18,19,52,20,103,55,76,21,23,29,40,87,88,111,54,26,65,28,115],radix:68,pred_begin:16,shouldexpandatomicstoreinir:86,saga:[13,47],"0x70b298":76,random:[68,32,24,1,67,83,25,42,112,70,16],radiu:101,popq:88,radic:84,dfapacket:[84,21],lit_config:1,absolut:[23,64,68,52,70,20,9,58,76,94,5,29],package_str:60,bitcoderead:64,createreassociatepass:[39,45,2,47,48],configur:[68,0,31,33,1,34,93,35,4,5,37,8,97,9,10,16,50,52,76,113,77,23,24,84,87,62,63,25,26,65],nextprec:[39,41,54,45,2,47,48],multiclassid:28,getreg:[84,52],llvm_yaml_is_sequence_vector:91,label0:70
 ,twiddl:[39,45,2,47,48,12,13,14,15,70],watch:[25,68],image_scn_type_no_pad:108,pointertyp:16,report:[30,31,33,1,93,36,70,66,37,40,41,10,16,19,103,76,77,83,24,61,63,88,26,90],reconstruct:[102,103,96],sparclet:52,aliasanalysisdebugg:40,start_val:[13,14,15],sunit:84,isoper:[39,45,2],basicblock:[30,39,23,41,32,45,2,47,48,76,74,68,13,16],stringwithcstr:103,lto_module_is_object_file_for_target:90,habit:[30,68],nuw:[70,49],memory_order_releas:[70,86],storesdnod:52,attributeset:56,richer:88,bitvector:16,nul:[14,16,2],num:[74,70,52],libsampl:50,corrupt:[107,38,11,24,96],dumpattr:21,hopefulli:[30,68,40,20,86,48,76,111,12,105],databas:[38,91,11],image_file_machine_mips16:108,discoveri:1,valb:8,tolmach94:74,mul:[30,8,41,5,102,115,70,19],approach:[30,68,101,52,102,32,20,84,85,103,83,10,90,78,73,69,16,29],weak:[16,29,45,86,90,49,111,32,110,15,70],protect:[68,52,24,84,103,86,111,4,70],notatom:86,critedge1:8,fault:[112,25,78],r7xx:104,"4gib":22,mybarflag:91,lto_module_cr:90,kwd:[12,13,14,15,17,18,1
 9],canlosslesslybitcastto:32,max_int_bit:16,trust:[25,68],nake:[70,111],nonsens:[15,45,105],getglobalcontext:[39,41,45,2,47,48,16],accumul:[30,0,24,12,13,14,15,18,19],fnloc:39,oldbind:[15,45,39],quickli:[23,61,96,37,74,83,20,40,103,62,10,35,68,65,4,84,70,24],getsymbolt:16,"0x000003bd":103,msec:0,xxx:[33,68,5,52],uncommon:107,expected_v:70,testcaselength:16,craft:16,"catch":[102,41,107,20,48,25,12,98,70,19],upcast:101,smallbitvector:16,image_sym_class_undefined_stat:108,simplevalu:28,bitcod:[30,84,32,67,35,36,70,37,7,95,96,8,112,44,92,16,97,100,75,64,76,77,80,110,23,106,83,29,61,87,63,25,111,65,90],basic_p:115,basic_r:115,lesser:78,curvar:[15,45,39],cumemalloc:8,mcsymbol:[74,84],cdecl:70,p_reg:84,image_sym_type_mo:108,svr4:[29,96],vk_argument:68,exterior:73,registermypass:76,tediou:91,list_property_nam:26,suggest:[76,23,68,40,70,9,62,25,99,16,6,50],armasmprint:21,ilp32:[38,11],disposit:25,dooneiter:83,complet:[30,84,32,1,67,93,94,35,68,4,70,71,37,39,8,41,112,43,45,2,47,48,10,72,49,73
 ,12,13,14,15,17,18,19,52,74,20,75,103,76,89,58,59,107,29,40,25,111,54,65,90,115],asan_opt:24,sched:[80,84,52],darwin9:5,binaryexprast:[39,41,54,45,2,47,48],build_ret:[12,13,14,15,19],introductori:37,property_nam:26,redefin:[115,41,29,45,2,14,15,19],sethiddenflag:20,image_scn_mem_not_pag:108,bugzilla:[37,31,73,93,10,25],shortli:39,memarg:46,everyth:[93,35,70,37,8,41,54,43,2,47,10,13,14,17,18,19,102,20,76,23,84,86,87,63,65],spencer:4,addend:70,makevehicl:68,setcurrentdebugloc:39,finalizememori:71,"0x01":[66,6,103],uncoop:74,meta:[74,16,29,84,103,88,70,6],numliveout:88,shorthand:115,"0x03":88,expos:[23,84,30,70,20,1,45,40,83,76,86,21,90,73,4,68,15,16,29],interfer:[107,49,102],patchpoint:[73,29,70,88],elf:[71,104,84,103,10,111,57,70],"0x7fffffffe018":98,type_symtab_block:111,els:[30,84,0,32,33,35,68,4,70,6,66,38,39,8,41,5,43,45,2,47,48,10,11,12,13,14,15,16,17,18,19,52,20,64,80,91,63,25,54],at_artifici:103,explanatori:33,elt:70,gave:32,xnor:52,setloadxact:52,disableencod:6,howtosubmitabu
 g:23,"______________________":16,thumb2:[84,56],gr64:84,end_:[13,14,15],apart:[60,16,78,40],unindex:52,arbitrari:[68,73,1,70,38,40,41,54,43,102,45,48,11,12,15,16,17,18,19,52,53,74,20,103,76,107,29,84,25,88,111,26,115],loadlal:70,contradict:25,build_add:[12,13,14,15,19],unstabl:[31,34],hung:16,ifexprast:[13,39,45,2,47],scopelin:39,llvm_use_sanit:60,excerpt:8,"000000e":[41,45,47,48,12,13,15,19],enumcas:91,indirect:[97,52,70,84,22,88,16],successfulli:[61,40,29,0,9,2,93,113,14],live_end:74,"0x401000":79,icc:[23,103,0],attrparsedattrimpl:21,guaranteedtailcallopt:70,optparserdef:21,armv7:[34,78,93],armv6:34,armv8:[104,6],registerclass:[84,21,6,52],core:[45,34,70,6,39,104,40,41,9,2,47,48,10,16,76,26,21,23,60,24,25,113],compiler_rt:25,tour:[54,18],subtmp:[39,41,45,2,47,48,12,13,14,15,19],cast210:70,meyer:68,chapter:[37,38,39,41,32,43,45,2,47,48,11,54,12,13,14,15,17,18,19],min_int_bit:16,canreserveresourc:84,surround:[30,102,5,86,88,70,6],unfortun:[38,68,32,29,46,47,48,76,11,12,13,16],distin
 ct:[30,111,102,40,41,5,29,84,10,70,26,65,16,19],g_inlined_into_f:79,algo:76,bitsetcas:91,approxim:[35,1],produc:[30,91,107,0,32,1,68,36,4,70,66,38,39,84,41,5,44,9,46,47,48,11,45,12,13,15,16,97,19,52,102,74,77,75,103,76,21,78,96,23,60,83,24,61,86,87,63,25,112,26,65,27,29],llvm_linker:29,addpsrr:115,ppa:23,instcombin:[30,97,16,83],regist:[30,91,0,73,5,98,70,6,71,39,84,8,41,112,97,45,2,47,48,49,12,13,14,15,16,19,52,74,77,75,76,21,78,80,23,82,107,29,40,25,88,113,27,114,115],encod:[91,32,36,70,6,66,37,39,96,45,15,16,52,103,77,78,80,23,107,84,88,111],othervt:52,parse_bin_rh:[12,13,14,15,18,19],createfmul:[39,41,45,2,47,48],objectso:65,storag:[8,74,16,20,84,103,111,70],addpsrm:115,git:[23,24,60,82,63],dw_apple_property_copi:103,x86targetasminfo:52,"class":[30,84,32,46,68,69,4,70,6,71,37,38,39,101,40,41,54,45,2,47,48,11,12,15,16,18,19,66,52,74,20,64,103,76,21,78,56,55,23,59,29,91,62,111,65,27,114,28,115],stuck:[38,11],reli:[68,102,0,31,16,24,84,45,103,10,74,25,90,78,73,65,15,70,58,97],gid:9
 6,image_sym_type_enum:108,synthesiz:29,sitofp:[41,70,19],synthesis:24,head:[23,68,74,28,105,70,115],medium:80,tokens_fil:24,unconvinc:24,modulepass:[76,40,8],p0i32:5,add_definit:60,heap:[38,59,40,74,70,24,91,45,11,85,88,15,16],icmp:[70,16,111],n2541:68,counsel:25,attr:[21,70,103,111],lsan:24,fundament:[64,84,52,102,73,20,56,81,76,68,32],autoconf:[23,60,52,29,97,87,93],loadregfromstackslot:[84,52],adorn:105,reachabl:[74,60,59,70,73],trig:52,eieio:70,"_ztv3bar":5,adjac:[70,16,28],rgpassmanag:76,assembl:[97,73,33,67,35,36,70,6,37,64,95,8,44,77,48,10,72,104,92,12,51,52,102,74,75,103,21,22,78,80,23,29,84,85,25,111,26,65,27,114],readonli:[30,73,103,88,49,111,70],tirefactori:68,when:[30,61,107,0,31,32,33,1,93,94,35,68,101,4,98,70,6,71,37,38,39,84,8,41,5,43,97,45,2,47,48,10,11,49,73,12,13,14,15,16,17,18,19,66,100,52,102,74,90,20,75,64,103,76,21,22,78,80,57,110,96,23,60,82,83,24,40,85,86,87,91,62,25,88,54,111,112,26,65,105,28,29,115],in32bitmod:84,tid:8,snapshot:40,node:[30,91,0,32,3,36,101,
 70,37,64,39,84,8,41,54,45,2,47,48,12,13,14,15,16,18,19,52,103,55,76,21,58,59,29,40],smallset:16,uint8:88,consid:[30,68,0,31,32,34,69,4,70,6,66,38,39,40,112,43,97,45,46,47,98,10,11,49,73,13,15,16,17,18,101,102,74,20,103,76,110,78,58,59,29,84,88,111,54,65,28,115],idx3:102,global_dtor:70,idx1:[70,102],idx0:70,uniformli:68,"0x0f":88,libcuda:8,faster:[23,68,96,32,24,34,103,83,107,113,65,70,16],bullet:[97,101],freebench:33,serious:35,offsetof:[38,11],backward:[0,74,20,25,111,56,16,29],getintrinsicid:74,impli:[23,52,40,74,28,84,87,25,88,70,65,79,4,102,16,89],focus:[84,52,73,44,10,16],catagor:30,movabsq:[88,85],signific:[64,68,111,40,74,16,24,43,2,47,76,25,90,29,78,32,14,70,17],computation:59,llc:[76,23,84,52,8,74,112,61,67,83,10,35,77,87,80,65,5],mips64el:[23,87],n32:[29,70],row:69,addregisterclass:[84,52],readabl:[23,84,95,106,30,92,91,68,103,86,76,25,36,65,105,70,89],getorcreatetypearrai:39,pop_back:[20,39,16],sourc:[61,91,31,32,33,1,67,93,94,35,68,4,98,70,6,66,37,38,39,8,41,5,97,9,77,48
 ,10,11,49,73,12,84,16,50,19,100,52,53,74,20,75,103,76,21,79,102,23,60,83,24,40,87,25,88,112,26,65,90,29],t1item:32,feasibl:[70,9],"00main":103,cool:[39,41,20,45,2,47,48,76,12,13,14,15,19],cuctxcreat:8,curop:52,level:[30,91,0,32,33,46,68,36,4,98,70,71,37,38,39,84,8,41,5,43,97,45,2,47,48,10,11,73,12,13,14,15,16,17,18,19,66,102,52,53,74,20,103,76,77,78,57,23,59,60,107,29,40,86,25,88,50,111,54,26,65,28,115],quick:[66,30,38,68,60,96,82,40,31,83,20,102,9,103,87,48,10,25,11,12,76],release_26:23,release_27:23,release_24:23,auroraux:29,"__builtin_longjmp":107,release_23:23,release_20:23,release_21:23,release_28:23,release_29:23,get_subtarget_feature_nam:21,magnif:[14,43,2,17],endcond:[39,15,45,2,47],port:[23,38,97,0,29,84,35,11,113,4],llvmlib:[65,50],"64bit":31,exitcond:70,alphajitinfo:52,eckel:16,u32:8,llvmld:65,declare_funct:[12,13,14,15,19],fmax:70,memory_order_relax:[70,86],testsut:65,fmag:96,dw_tag_restrict_typ:103,preorder:101,nondebug:30,createbasicaliasanalysispass:[39,45,2,47,48],wr
 itethunk:32,switchsect:[74,84],strtod:[39,41,54,20,45,2,47,48,43],r6xx:104,add_librari:60,dorit:0,weird:84,automaton:[84,21],semant:[91,73,68,4,70,6,8,41,97,47,49,99,13,16,19,74,103,76,21,59,107,29,84,86,88,26,27,90],targets_to_build:[9,52],builder_at:15,globallayoutbuild:55,tweak:[62,23,20,101],visibl:[59,96,8,16,20,84,68,103,86,76,90,111,73,70],memori:[30,61,0,73,1,34,68,70,97,71,38,39,84,8,112,43,44,45,46,98,11,49,72,15,16,17,52,102,74,64,103,76,21,78,55,59,60,24,40,85,86,91,88,27,90,29],camlp4of:[12,13,14,15,18,19],pred:[8,70,45,47,13,15,16],preg:[24,84],pref:[70,29,16],todai:[68,86,102],handler:[107,29,84,70,86],upheld:73,instalia:84,criteria:93,msg:70,andw:5,prev:16,reorder:[5,29,86,103,73,70],plug:[41,19],capit:68,share:[30,91,73,33,68,69,4,70,6,39,8,41,112,97,9,2,98,10,84,16,50,19,103,76,77,80,23,60,83,29,61,86,87,62,111,65,90],drown:33,prototyp:[30,7,39,52,41,54,103,45,2,47,48,76,68,64,12,13,14,15,70,18,19],build_br:[13,14,15],ccassigntoregwithshadow:52,registerinfo:[84,21,
 52],function_typ:[12,13,14,15,19],purpos:[30,68,31,32,4,70,6,39,8,41,48,99,16,102,20,103,76,21,78,23,84,87,25,65],explor:[29,16,82],preemptibl:30,sidelength:101,parse_binary_preced:[14,15],add8rr:84,critic:[30,68,40,31,54,93,76,74,80,18],alwai:[30,84,33,1,68,3,36,4,70,66,7,39,96,40,41,5,97,45,2,47,48,10,11,49,12,13,14,15,16,50,19,101,102,20,38,103,78,23,59,82,107,91,25,111,54,26,65,90],differenti:[26,4,82,65],stepval:[39,45,2,47],twoargfp:115,anyon:[29,25,103,52,86],fourth:[52,20,76,88,13,70],cstptr:70,"__nv_isinff":8,no_switch:0,double_typ:[12,13,14,15,19],clone:[23,24,1,45,76,63,21,15,16],mcdisassembl:84,interconnect:29,geforc:8,testresult:37,colfield:69,practic:[30,68,70,41,43,97,47,48,12,13,16,17,19,102,74,20,103,59,24,86,25,88,29],firstlett:98,calltmp6:[15,45],predic:[68,52,86,21,78,69,70,6,115],the_fpm:[12,13,14,15],cse:[12,64,59,86,48],destmodul:65,preced:[30,68,1,70,39,40,41,54,43,45,2,47,48,12,13,14,15,16,17,18,19,53,103,110,88,28],combin:[30,84,0,32,93,94,36,70,38,41,54,10
 2,11,73,16,18,19,52,53,74,20,64,76,22,60,83,29,91,25,111],practis:58,image_file_machine_amd64:108,sphinx_execut:60,blocker:31,ymmv:68,microscop:68,size_t:[74,24,91,90],synthesizedcd:78,canari:70,fsanit:24,foo_dtor:46,gte:70,branch_weight:[3,58],pinsrd:5,platform:[34,93,35,4,70,37,104,97,9,2,48,10,12,16,74,76,113,23,60,29,84,86,87,62,25,88,26,65,90],gtu:8,getsymboladdress:49,ymm0:88,debug_abbrev:89,unswitch:30,maskedbitsetcas:91,flagspointi:91,technic:[37,24,25],sourceleveldebug:39,term:[30,59,107,37,73,28,40,68,103,86,10,25,88,78,32,4,84,70,97,115],name:[1,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,29,25,26,27,28,30,31,32,33,35,36,38,39,41,54,43,44,45,2,47,48,50,52,53,103,60,91,64,65,69,70,66,72,74,76,77,79,80,106,84,87,88,90,68,92,93,94,95,96,97,98,100,101,102,55,114,82,107,108,109,110,111,112,113,105,115],getoperatornam:[39,45,2],realist:[74,54,18,115],cellspac:84,sequentiallyconsist:86,callsit:[30,16,88,107],varexprast:[39,45],the_execution_engin:[12,13,14,15],individu
 :[30,68,33,1,35,36,70,37,64,39,96,10,49,16,78,23,83,25,111,26,27,115],otherspecialsquar:101,const0:111,getdoubleti:[39,41,45,2,47,48],hacker:[37,25],armneon:21,profit:[30,84,49,0],decimalinteg:28,hasloadlinkedstorecondit:86,profil:[66,23,87,82,30,97,103,67,109,3,49,65,70,50],sctx:24,roundp:0,iscxxclass:103,factori:[30,64,68,16],aliase:[32,70,111],"\u03c6":70,migrat:[29,25],write_escap:76,integertyp:16,theori:[32,38,91,11],getvalueid:32,boehm:74,synchron:[90,70,86],refus:[23,7,60,106,30,92,75,95],motion:[23,59,40,76,30,70],turn:[30,68,73,70,6,38,96,41,54,97,11,99,83,18,19,52,74,20,64,103,78,16,84,86,62,65,105,90],place:[30,84,0,31,32,1,68,70,6,66,38,96,41,54,43,45,2,48,10,11,73,12,14,15,16,17,50,19,52,102,74,20,64,103,76,113,78,80,23,83,29,91,87,63,25,88,107,26,65,115],ture:[12,54,18,48],imposs:[38,52,40,86,25,11,78],origin:[23,39,96,102,53,73,70,29,84,103,87,94,107,99,65,4,5,6,16],suspend:74,redhat:62,arrai:[30,84,0,32,70,66,38,96,8,54,45,10,11,49,12,13,14,15,16,18,19,52,102,74,103,
 21,22,78,107,24,40,111],number1:32,bou_fals:20,transform:[30,68,32,69,5,6,37,64,39,40,41,70,97,45,2,47,48,73,12,15,16,50,19,52,74,75,103,76,21,23,60,83,84,86,88],rodata:52,readattribut:21,predefin:[76,14,1,2],unrecogn:20,"0x00003550":103,given:[30,84,73,1,35,68,36,101,4,70,71,64,96,40,41,54,44,2,14,16,97,18,19,52,53,20,75,103,55,76,21,79,58,23,60,107,24,91,86,109,63,88,111,26,65,28,115],frameindex:52,image_sym_class_external_def:108,assort:39,necessarili:[23,68,102,31,97,103,39,70],llvm_int_ti:64,circl:101,white:104,cope:[20,16],copi:[30,84,0,73,93,94,68,70,71,8,5,97,9,46,10,16,100,52,74,20,103,76,80,23,59,60,83,40,85,63,111,65,105],dblty:39,image_scn_mem_execut:108,enclos:[68,5,10,88,111,16,115],pragma:0,grunt:20,releasei:31,serv:[30,102,37,16,29,1,103,10,88,78,65,28],wide:[34,86,70,37,38,8,47,48,11,12,13,16,102,74,103,23,29,84,40,111,65,28,115],image_sym_type_doubl:108,subexpress:[39,40,54,45,2,47,48,76,59,12,13,14,15,18],getoperationnam:64,posix:[110,60,96],balanc:[25,86],posit:[
 23,90,84,107,70,20,91,9,2,47,80,25,88,111,65,69,13,14,5,18],ebp:[84,6],xxxgenasmwrit:52,seri:[23,84,60,16,43,61,48,76,58,25,111,107,12,104,70,17],pre:[66,23,64,25,30,31,24,61,93,80,41,21,59,65,84,16,6,50,19],pro:78,isfunct:103,subroutin:[74,103],doiniti:[39,52,74,45,2,47,48,76],bitwis:[30,70],techniqu:[0,32,70,40,54,43,45,2,47,48,12,13,14,15,83,17,18,52,74,76,16,24,84],ebx:[84,22,6],moreov:[30,84,70],datapath:29,codegen_proto:[12,13,14,15,19],instrprof:70,sure:[84,0,31,9,34,93,94,68,4,6,38,39,40,41,54,97,45,2,47,48,10,11,49,99,15,16,19,101,20,64,103,76,78,23,60,82,24,61,86,62,63,25,113,65],multipli:[30,64,59,16,84,70,58],"__asan_memcpi":24,clearer:68,fca:59,nproc:23,gunzip:[23,35],fco:52,bb0_30:8,later:[30,68,32,33,94,70,71,39,41,5,48,10,12,13,14,15,16,50,19,66,52,103,76,23,29,84,88,18,54,65,105],quantiti:70,mybison:33,runtim:[30,84,0,73,4,98,70,66,38,104,2,48,11,14,83,52,74,20,103,76,23,16,29,91,85,87,25,88,107],readjust:84,xxxasmprint:52,cs2:40,cmakelist:[60,53],apple_namespac:103
 ,build_cal:[12,13,14,15,19],uncondit:[30,52,47,94,13,14,15,70],dw_lang_cobol74:103,cheap:[68,16,86],permiss:[71,23,25,96,113],hack:[30,38,39,43,9,76,11,17],culinkst:8,tend:[23,68,102,31,44,103,25,26,16],explicitli:[30,68,0,73,33,5,71,38,40,41,70,97,46,11,16,19,102,20,23,60,84,87,115],lua:74,derivedtyp:[64,39,41,45,2,47,48,16],written:[30,61,0,32,94,68,36,4,109,70,7,39,8,43,97,2,47,10,11,92,13,14,84,16,17,52,53,38,103,21,22,24,40,91,25,26,65,29,115],sk_circl:101,analyz:[30,75,23,32,33,65,103,47,76,67,35,21,49,36,13,84,16],abs_fp32:6,analys:[30,64,75,37,16,40,103,76,23,84,70,58],llvm_scalar_opt:[12,13,14,15],mcsectionmacho:84,jazz:50,ssp:[70,103,111],module_code_gcnam:111,allocat:[84,70,52],ssl:24,dyn:57,tailor:34,image_comdat_select_largest:70,use_llvm_executionengin:[12,13,14,15],sse:[84,70,52,56],regtyp:52,ssa:[30,38,59,52,41,70,43,84,45,2,47,74,97,11,73,13,14,15,16,17,19],dw_tag_packed_typ:103,reveal:102,"0x00002023":103,dramat:[68,20,48,77,12,70],intrins:[30,64,107,52,8,74,16,29,
 0,85,103,86,21,37,49,78,73,88,55,114,70],fastcc:[29,84,70,97,111],bison:33,scott:68,backedg:[30,2,47,13,14,58],drawback:[20,25,16],n16:8,rmw:86,noth:[76,30,102,74,70,43,84,45,10,65,4,15,16,17],labori:16,deadargelim:30,atomic_:86,detect:[30,44,60,82,0,5,24,1,103,48,70,32,12,16],mov32ri:84,review:[37,68,82,23,32,93,35,25,49,73,4,105],get_register_match:21,cudamodul:8,image_scn_cnt_uninitialized_data:108,abs_f:6,cycl:[90,29,70],isatleastacquir:86,bitset:[91,55,52],collect2:63,come:[84,32,94,68,69,70,38,96,8,41,112,43,45,46,47,48,10,11,12,13,15,16,17,50,19,102,74,64,103,76,23,60,24,91,25,111,115],latch:70,at_apple_runtime_class:103,region:[66,30,59,107,76,88,111,70],quiet:[65,20,1,98],contract:[88,21,70,101],nocaptur:[30,70,111],entir:[30,61,0,33,1,94,68,36,70,38,96,8,41,97,48,10,11,12,84,16,19,52,102,74,20,103,76,78,23,40,91,25,111,26,65],image_scn_mem_purg:108,imgrel:22,image_file_machine_powerpcfp:108,nnn:96,color:[66,84,16],pow:[8,70,0],rescan:32,inspir:[30,70],period:[10,83,24,25,7
 0],pop:[39,74,70,84,45,47,111,13,15,16],hblcnsviw:20,image_file_machine_sh4:108,image_file_machine_sh5:108,colon:[60,91,10,26,5,115],image_file_machine_sh3:108,dw_form_ref4:103,coupl:[38,39,16,2,47,86,76,25,11,13,14,70,90,115],pend:[23,39,98,41,54,45,2,47,48,12,13,14,15,18,19],test_source_root:1,sectionnumb:108,"abstract":[30,84,73,68,4,70,6,39,101,41,54,43,97,45,2,47,48,49,12,13,14,15,16,17,18,19,52,74,103,76,59,91,111,90],ounit:29,debug_str:103,savesomewher:68,variableexprast:[39,41,54,45,2,47,48],mytype1:91,andrew:74,mytype2:91,mrmdestmem:52,instrssrr:115,intertwin:59,"case":[30,91,0,32,33,68,34,67,46,3,69,4,54,70,6,71,37,7,39,84,40,41,5,43,97,9,2,47,48,10,11,49,45,12,13,14,15,16,17,18,19,66,100,52,101,74,90,20,75,38,103,76,21,78,102,96,23,60,73,112,24,61,85,86,87,83,55,25,88,50,111,64,65,27,105,28,29,115],addimm:84,module_code_alia:111,push_back:[39,52,41,54,91,45,2,47,48,68,16],stackgrowsdown:52,registerwithsubreg:52,dw_apple_property_weak:103,type_code_point:111,cast:[28,38,39
 ,101,102,70,20,45,2,47,48,68,11,78,32,12,16,6,115],tblgen:[64,60,52,84,9,67,21,65,114,6,115],anytim:97,emittrailingf:86,isextern:103,good:[30,84,31,32,33,34,93,68,4,6,64,104,8,41,112,45,2,47,48,12,13,14,15,16,52,20,103,76,23,83,29,40,25,27,24,115],clutter:25,image_file_up_system_onli:108,rangepiec:28,d14:52,d15:52,addedcomplex:6,value_desc:20,d10:52,d11:52,d12:[55,52],d13:52,alphabet:65,ubsan:24,trip:[30,68,70,78,0],html:[23,64,39,60,31,112,24,84,9,87,93,41,21,68,33,19],intreg:[69,52],eventu:[30,101,70,33,46,47,73,13,5],hasadsizeprefix:6,week:25,image_sym_class_label:108,nest:[84,52,0,74,107,103,1,40,47,46,76,68,54,111,65,26,13,105,70,18,115],confidenti:25,driver:[39,104,8,41,54,24,43,45,2,47,48,10,50,12,13,14,15,90,17,18,19],driven:[30,38,52,40,20,84,45,48,10,11,12,15,5,17],devoid:84,setversionprint:20,viewgraph:16,moder:[68,16,82],justifi:[90,96],iterat:16,"__main":76,model:[91,0,73,1,68,69,70,37,84,41,54,97,45,46,15,16,18,19,52,102,74,20,103,21,22,80,29,61,86,111,90],customreadba
 rri:74,unimpl:[76,68],tip:[23,38,25,37,29,43,76,21,11,49,83,17],s_waitcnt:72,"0x000003f3":103,redwin:84,kill:[76,112,84,83],xxxbranchselector:52,dynamic_cast:[45,68,39,16,101],blow:24,miscellan:[104,96,33,20,76,70,29,50],widest:25,hint:[68,0,41,16,102,83,79,70,19],except:[30,91,32,1,46,68,36,4,70,37,38,95,84,8,41,5,43,45,2,48,11,49,12,13,14,15,16,17,18,19,52,102,20,76,21,78,80,96,60,107,29,40,86,88,111,26,65,28,115],cxx:[23,31,97,9,87,63,65],blob:[31,111],notori:4,disrupt:[105,70],image_sym_dtype_point:108,predrel:69,subtargetfeatur:[6,52],createbr:[39,45,2,47],image_sym_class_union_tag:108,"0x000003ff":84,saniti:[26,23,65],"0x1000":103,whitespac:[23,39,41,28,43,45,2,47,48,25,68,54,12,13,14,15,5,17,18,19],image_scn_align_256byt:108,cooper:[74,63],targetinstrinfo:[84,52],evergreen:104,deduct:68,trampolin:70,at_apple_property_attribut:103,freez:[97,93],slice:[28,16,115],gvn:[30,39,40,45,2,47,48,76,86],easili:[76,23,61,30,74,32,20,53,9,103,91,10,68,88,49,73,26,4,84,16,29],benefici:0,le
 gal:[23,64,52,8,16,29,84,86,87,10,25,49,73,27,102,70],gridsizex:8,encodecompactunwindregisterswithoutfram:84,gridsizez:8,derferenc:16,freea:46,libfil:100,freed:[85,16,40],garbag:[37,38,59,43,74,73,29,97,11,111,88,70,17],inspect:[102,16,84,103,76,49,111,54,70],boolordefault:20,oneargfprw:115,immut:[76,70,16,56],execv:4,stacklet:85,mergabl:30,cmptmp:[39,41,45,2,47,48,12,13,14,15,19],stanc:68,cuda:[29,84,104,8],image_scn_align_16byt:108,onon:70,routin:[30,38,84,74,32,43,1,48,76,25,11,54,12,4,16,17,18],clangdiagsdef:21,dw_at_nam:103,tbcc:52,lastli:[10,76,39,56],overrod:115,idx2:102,cpu_powerpc:91,possbil:91,unconvent:[38,11],classess:52,fcc_g:52,getbuff:91,strict:[41,32,103,5,49,78,99,26,16,6,19],interfac:[30,84,32,1,68,69,4,98,70,37,38,104,8,41,54,43,97,48,11,12,16,17,18,19,52,74,20,103,76,21,56,23,60,82,24,40,63,88,26,90,29,115],mm4:[6,115],strictli:[23,8,73,70,65,103,47,74,13,4,5],blocklen_32:111,machin:[68,0,32,1,34,94,98,70,71,37,38,39,8,5,9,48,11,49,73,12,16,52,74,103,76,21,22,78,
 80,23,59,60,84,108,87,77,113,114],fcc_u:52,"__llvm_coverage_map":66,timelin:93,tupl:70,regard:[37,68,97,46,93,21,70],ocaml_lib:[12,13,14,15,19],mm0:[84,6,115],setjmp_buf:107,stackmap:[29,88],mm3:[6,115],getdata:68,longer:[30,68,96,74,29,84,45,105,76,25,56,15,16,97,50],cmakecach:60,nmake:60,runonregion:76,parsetoplevelexpr:[39,41,54,45,2,47,48],handletoplevelexpress:[39,41,54,45,2,47,48],make_uniqu:[39,45,2,47,48],dstindex:52,x86_stdcall:84,clrq:84,clrw:84,cbe:61,frighten:24,strongli:[38,59,74,9,45,47,68,11,13,15,115],clrb:84,intro:[37,15,45,104],deletevalu:40,umax:70,encompass:[34,56],rearrang:59,intra:40,tok_eof:[39,41,54,43,45,2,47,48],clrl:84,incorrect:[39,41,29,61,45,2,47,48,12,13,14,15,70,19],call2:5,multiclass:[28,6,52,115],idiom:[41,20,16,19],symbol:[30,84,45,67,68,36,98,70,71,38,39,96,40,41,9,2,47,48,11,73,13,14,15,16,19,52,74,20,103,110,22,79,80,57,23,59,29,91,108,87,62,111,65,90,115],briefli:[66,32,76],mrmsrcreg:52,lexicalblock:39,llvmcreatedisasm:27,buildmi:84,ilist_nod:1
 6,getdisplaynam:103,callq:[88,85],directori:[68,31,33,1,93,94,35,4,6,37,39,97,9,10,16,50,100,52,103,76,113,23,81,60,24,84,87,63,25,26,65,114,29],invest:64,calle:[30,32,46,70,39,41,54,97,45,2,47,48,73,12,13,14,15,19,52,76,78,84,88,115],potenti:[30,68,73,1,93,70,40,54,43,97,47,49,13,83,17,18,20,23,107,24,84,25,88,29],degrad:74,"__sync_":86,"0xl":70,metatada:3,all:[0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,23,24,25,26,28,29,30,31,32,33,34,35,36,37,38,39,40,41,112,43,44,45,46,47,48,49,50,52,57,59,60,61,63,64,65,91,67,69,70,71,72,73,74,75,76,77,78,79,80,83,84,86,87,88,89,90,68,93,94,96,97,98,100,101,102,103,82,107,109,110,111,54,113,114,115],replacealluseswith:[32,59,16],dist:[23,16,87,65],fp_to_sint:52,lack:[102,74,70,84,62,99,12,28,6,115],scalar:[30,39,52,0,74,84,20,91,45,2,47,48,59,26,15,70,29],basicblockutil:16,pty:70,ptx:[84,104,8],follow:[30,61,107,0,31,32,33,1,34,67,93,94,68,36,69,4,54,70,6,66,64,39,95,84,8,101,5,43,97,9,2,47,98,10,45,13,14,15,16,17,18,52,102,74,90,2
 0,103,76,113,110,22,78,96,23,60,82,73,83,29,40,86,87,91,62,63,25,88,50,111,112,26,65,27,105,28,115],spcc:52,ptr:[68,52,8,16,55,88,70],printinformationalmessag:20,uint8_t:[24,91],getaddressingmod:52,init:[23,39,20,45,76,15,70,24],program:[30,61,107,0,73,33,1,77,67,94,35,68,4,98,70,6,66,37,7,39,104,84,8,101,5,43,97,45,47,48,10,11,55,12,13,15,16,17,18,102,52,53,74,54,20,75,38,103,76,21,89,79,80,57,96,23,59,83,24,40,87,91,62,63,25,88,50,111,112,65,114,90,29],neglig:24,deepcheck:16,lsbit:16,far:[38,40,41,70,20,45,2,103,76,11,54,64,26,14,15,16,29,18,19],faq:[37,38,24,97,11,70],urem:[64,84,70],sparingli:49,worst:[16,38,11,85],toolbuildpath:65,failur:[76,23,61,91,31,5,33,1,34,87,103,10,35,25,83,70,112,93,16,17,18],fab:[70,0],unoffici:102,experimental_dir:65,isunpredicatedtermin:52,basicaliasanalysi:[76,30,40],subsubsect:105,feat_reli:84,lisp:[74,38,11,29],sectionnam:111,list:[30,61,54,0,31,32,101,1,77,67,93,115,3,36,69,68,98,70,6,97,71,37,38,39,104,84,8,41,112,43,44,45,2,47,48,11,73,12,13,1
 4,15,16,17,18,19,100,52,53,74,90,20,75,64,103,76,21,56,80,110,96,23,59,60,82,83,29,40,85,86,87,91,62,25,88,50,111,107,26,65,27,114,28,105,89],lli:[23,112,61,67,98,76,35,77,80],llvmdev:[37,38,68,73,86,25,11,49,28,115],ten:102,use_llvm_analysi:[12,13,14,15,19],eas:34,still_poison:70,libfuzz:24,tex:33,rate:[25,96,111,36],pressur:[84,68,0],design:[30,84,73,33,1,5,68,4,70,6,71,37,38,40,112,43,97,45,46,98,11,99,15,16,17,50,66,102,52,53,74,20,103,76,113,56,57,59,83,24,91,86,25,88,111,107,26,90,29,115],storageclass:108,hasard:74,proxi:84,what:[30,61,91,31,32,33,77,67,93,35,68,4,70,6,37,38,39,84,8,41,5,43,97,9,2,47,48,11,99,45,12,13,14,15,16,17,18,19,52,102,54,20,75,64,103,76,113,21,78,58,96,23,59,60,82,106,73,83,24,40,86,87,63,25,50,111,107,26,65,105,28,29,115],namedindex:52,sub:[32,1,5,6,66,64,41,70,10,16,19,52,103,21,22,23,84,86,87,25,111,65,115],sun:[10,76],sum:[0,16,94,111,70,58],brief:[23,68,60,40,74,32,20,61],tailcallopt:[84,70],asmprint:[74,84,21,52],version:[84,0,32,93,94,35,68,36,9
 8,70,66,38,39,104,8,41,5,97,45,47,48,11,73,12,13,15,16,19,100,52,20,64,103,76,80,57,23,60,82,106,29,40,87,62,63,25,88,111,113,65,27,114,28],intersect:68,ctpop:[70,52],themselv:[84,16,20,1,103,25,54,111,32,26,65,70,6,18],behaviour:[68,0,20,10,22,78],xmm3:[6,115],shouldn:[71,68,40,20,9,17,65,70,43],jitcompilerfn:52,xmm6:[6,115],roots_iter:74,xmm4:[6,115],xmm5:[6,115],build_config:35,xmm8:6,xmm9:6,asmpars:[23,64,21],misinterpret:[68,83],slave:113,instrsdrm:115,observ:[38,68,73,84,86,11,70],xmm2:[6,115],magnitud:70,"0x0000006e":103,filenam:[68,92,5,36,42,6,66,7,39,95,112,100,20,75,103,77,89,80,57,60,106,109,110,65,114,115],heurist:[30,15,70,84,45],sparcasmprint:[84,52],dump_modul:[12,13,14,15,19],hexadecim:[20,91,110,22,70,115],proceed:[74,23,84],normalizedpolar:91,coverag:[66,37,24,67,94,25],metadata_block:111,qch:60,forcefulli:102,llvmtargetmachin:52,flat:91,at_apple_property_sett:103,cxa_demangl:103,isload:84,"80x86":113,flag:[84,0,31,32,68,69,70,8,5,9,98,10,49,12,13,14,15,19,100,52,
 74,20,103,79,23,60,24,91,87,62,63,88,65],stick:[68,16,34],"0x00000067":103,known:[30,91,31,73,33,93,35,68,70,37,39,84,8,41,112,43,45,2,47,48,49,99,12,13,14,15,16,17,18,19,52,102,76,23,107,40,85,87,50,111,54,115],ensu:52,valuabl:[33,25],outlin:[76,91],outliv:[30,24,70],caveat:39,relocationtyp:52,dmpqrtx:96,image_scn_align_8192byt:108,ppc64:84,reevalu:28,dicompositetyp:39,pong:32,bjarn:16,invokeinst:16,operandti:84,goal:[66,25,84,102,0,74,32,29,43,45,105,21,88,65,26,4,68,15,90,17],divid:[30,64,70,33,84,10,36,4,5,58],rather:[30,68,31,1,34,35,70,39,40,54,97,49,18,52,102,74,103,76,58,84,25,111,28],anxiou:60,hash_map:16,divis:[14,84,70,2],llvmgccdir:33,targetasminfo:[74,52],goat:68,replacewithnewvalu:40,resourc:[76,104,20,16],algebra:[30,70],mccontext:84,ranlib:[23,65,63],reflect:[23,52,40,8,2,93,76,14,90],okai:[39,102,41,54,45,2,47,48,68,13,12,4,14,15,70,18,19],ptxstring:8,"short":[91,1,35,68,70,66,39,8,97,45,2,47,13,14,15,52,78,79,23,84,40,25,88,114],postfix:68,unhid:20,stash:101,ambigu
 :[101,54,20,2,10,14,28,18],height:66,callback:[52,40,74,84,88,16],prepass:84,fslp:0,headlight:68,runonscc:76,geomean:0,next_var:[13,14,15],dso_path:77,style:[68,1,70,66,37,38,96,40,5,45,11,15,16,50,101,74,20,21,22,80,83,84,86,25,18,54,26,28,115],lai:[39,102,70,84,45,2,47,48,68,55,12,13,14,15,16],harmless:30,anachronist:111,retti:111,might:[84,32,68,93,35,3,4,70,38,96,40,101,5,97,9,47,11,73,13,14,15,16,50,52,74,20,99,103,21,23,59,60,83,24,91,86,25,26,65,27,105],alter:[76,65,20,97,70],wouldn:[68,15,45,39],"return":[30,91,0,32,68,46,94,35,3,69,4,98,70,71,38,39,84,8,41,42,43,97,45,2,47,48,11,49,73,12,13,14,15,16,17,18,19,66,52,74,101,20,64,103,76,21,78,56,79,80,57,96,23,83,24,40,85,86,87,109,55,25,88,54,111,107,65,27,105,90,29,89],no_instal:65,var_nam:[13,14,15],framework:[30,64,45,84,37,41,70,33,40,43,2,103,76,74,14,15,16,17,19],preheaderbb:[2,47],somebodi:25,bigger:[91,68],strr:52,complexpattern:[84,52],sourcebas:37,module_code_sectionnam:111,blockdim:8,"__dwarf":103,refresh:90,const_
 float:[12,13,14,15,19],difficult:[39,40,16,20,68,2,86,25,90,14,105,70],truncat:[70,52,115],compriz:36,nightli:[37,31,33,93,10,25],dcmake_cxx_compil:24,weight:[37,29,3,70,58],"2x3x4":70,stkmaprecord:[73,88],compute_20:8,linkag:[23,39,8,41,16,29,44,103,49,111,32,79,84,70,19],regmapping_f:84,asmparsernum:114,expect:[30,84,32,33,1,68,94,35,3,4,70,39,40,41,5,43,102,45,2,47,48,10,12,13,14,15,16,17,18,19,53,74,20,103,76,21,78,56,58,23,24,91,85,86,25,88,111,54,26,28,29,115],atom_count:103,constindex:88,suppos:[84,101,32,91,76,107,26,4,70],foolproof:76,ccifinreg:52,lineno:39,image_file_line_nums_strip:108,benjamin:74,isempti:16,uncommit:23,advanc:[66,51,39,52,74,16,20,68,48,76,25,54,12,105,70,24,18],guess:60,teach:[41,64,43,17,19],flagflat:91,thrown:[107,70],targetinfo:52,putchar:[39,41,45,2,47,48,12,13,14,15],thread:[30,84,60,8,74,16,24,1,85,40,86,111,73,98,70,29],vararg:[41,16,84,111,70,19],toolnam:[65,50],runtimedyldelf:71,machineframeinfo:84,ccifnotvararg:52,circuit:[14,2],precal:74,libc
 lc:25,bitpack:10,feed:[13,103,47,40],notifi:[25,93,40,0],ystep:[14,2],feel:[38,68,40,41,83,29,43,25,11,49,70,17,19],cuda_success:8,add16mi8:6,smallptrset:16,release_25:23,cond_val:[13,14,15],construct:[30,84,73,46,68,69,70,38,39,96,40,41,54,43,97,45,2,47,48,11,12,13,14,15,16,17,18,19,52,20,64,103,76,21,23,29,91,86,87,111,65,105,28,115],stdlib:23,blank:[38,68,96,54,43,25,11,105,17,18],slower:[68,74,32,84,107,16,97],fanci:33,my_jit_tool:65,superpos:16,script:[23,97,52,53,31,112,20,1,34,87,93,10,74,21,25,65,76,33,50],interact:[71,30,38,39,60,82,52,70,20,84,103,83,76,86,11,54,73,16,33,18],parsetyp:64,stori:[66,23,35],gpu:[37,104,52,8,29,21,72],gpr:[27,84,115],luckili:74,option:[30,61,0,31,32,1,77,34,67,93,115,94,35,68,36,98,70,6,71,37,7,39,95,84,8,41,5,44,9,2,47,48,10,42,45,13,14,15,16,97,50,19,66,100,52,53,74,90,20,75,103,76,21,78,56,79,80,57,110,96,92,23,60,106,109,83,24,40,87,91,62,63,25,88,111,112,26,65,27,114,28,29,89],iftru:70,syncthread:8,wswitch:68,st_gid:96,cmake_c_flag:60,mcas
 mpars:84,secondcondit:16,dsym:79,albeit:[15,45],kind:[30,68,32,3,36,70,6,66,39,96,97,45,2,14,15,16,101,74,20,103,21,56,77,107,24,84,86,25,88,26,65,105,90],assert_valid_funct:[12,13,14,15,19],doubli:[85,16],setgraphattr:16,remot:[71,23],remov:[30,84,32,93,94,68,101,4,70,7,39,96,8,41,5,97,45,2,47,48,11,49,73,12,13,16,52,20,75,38,103,76,77,56,92,23,59,60,83,29,40,87,62,25,107,65,90],empty_subregsset:52,valuesymbolt:16,dinkumwar:16,cleaner:[20,68,16],body_v:15,nnan:70,peculiar:28,ysvn:93,astwrit:21,dedic:52,"0b000100":52,check:[30,91,0,31,32,33,1,34,93,35,68,70,66,38,39,84,8,41,5,43,9,2,47,48,10,11,49,45,12,13,14,15,16,17,18,19,101,102,54,20,103,76,96,23,60,73,107,29,61,85,86,87,63,25,88,112,113,65,105,90,115],violat:[68,102,74,47,25,13,70],intregsclass:52,paramidx1:111,paramidx0:111,exec:[112,24],unsur:28,english:[23,68],reach:[30,68,52,74,32,29,88,26,70],flagsround:91,disttarbz2:65,shouldexpandatomicloadinir:86,image_rel_amd64_addr32nb:22,amaz:[14,2],dw_tag_enumeration_typ:103,xmm7:[6
 ,115],blockid:111,destruct:[88,38,11,46],libopag:62,sandybridg:0,arg_empti:16,ctag:21,rtl:84,getcol:39,intti:70,optimizationlevel:20,inapplic:34,brtarget:52,penalti:[70,16],dw_apple_property_retain:103,write_regist:70,bfd:63,create_add:19,image_file_large_address_awar:108,hash_funct:103,stackoffset:74,shlibext:[10,65],address_s:8,pushfq:84,"0x0001023":103,hit:[68,58],aliasopt:20,spurious:10,mydoclist:91,mydoclisttyp:91,fastest:113,sizabl:16,stdcall:[84,70],sextload:[6,52],him:32,exactmatch:70,llvmdummi:52,sk_otherspecialsquar:101,getvaluetyp:52,getpointertonamedfunct:71,"0x1234":103,use_empti:16,arr:[70,16,102],stump:52,dump:[39,111,41,83,24,91,45,2,47,48,76,103,21,89,36,12,13,84,16,19],cleverli:78,shared_librari:[65,50],proactiv:[25,83],mutabl:[51,39,43,45,2,47,13,14,15,70,17],arc:[94,82],dumb:[38,11],arg:[68,73,1,98,70,39,41,112,43,45,2,47,48,32,12,13,14,15,17,18,19,20,80,61,109,54,28],unreserv:103,disadvantag:[90,20,16,56],icc_:52,unqualifi:84,arm:[23,104,52,37,29,84,9,34,87,86,1
 0,21,22,78,27,70],property_valu:26,simultan:[23,0,87,10,78,16],setupmachinefunct:52,inconveni:[15,45,97],inst_end:16,old_valu:15,maprequir:91,pubtyp:103,condv:[39,45,2,47],extensioan:31,syntact:[12,70,29,5,48],unabbrev:111,sole:[25,16],aspir:[14,2],setbid:111,succeed:[76,1,70,58],outfil:42,solv:[38,102,40,84,45,2,103,25,11,93,14,15],setindexedloadact:52,v128:[70,8],isdopcod:64,interprocedur:[76,30,90,70,40],fragement:73,blissfulli:20,isomorph:97,available_extern:[70,111],context:[91,32,68,70,6,39,8,41,54,97,45,2,47,48,10,49,12,13,14,15,16,18,19,101,102,20,103,76,21,59,82,107,29,40,86,113,27,28,115],subclassref:28,internallinkag:16,tgt:114,getsrc:23,die_offset_bas:103,sweep:74,lbar:84,arbitrarili:[101,13,70,103,47],mistak:68,java:[30,38,74,70,86,11,16],due:[28,59,84,40,31,5,61,68,34,98,74,3,90,49,32,107,73,70],whom:32,brick:32,whoa:[12,48],strategi:[45,20,15,70,84],thunk:[30,84,32],flight:70,append_block:[12,13,14,15,19],llvm_map_components_to_librari:60,feat_tailcal:84,demand:[23,15
 ,45,84,111],instructor:52,asmmatcheremitt:21,echocmd:65,eatomtypedietag:103,frozen:98,batch:35,dagtodagisel:64,abov:[30,91,31,32,33,68,69,54,70,6,71,38,39,84,40,41,5,43,97,9,2,47,48,10,11,49,45,12,13,14,15,16,17,18,19,52,102,74,101,20,64,103,76,78,79,58,96,23,60,61,85,88,50,111,112,27,105,90,115],cmp32ri:84,getlinenumb:103,int32:88,runonfunct:[52,40,74,16,76,83],image_file_machine_am33:108,rip:[10,6],x8b:108,demot:30,rid:32,illinoi:[25,68,97],mioperandinfo:52,dw_lang_c:39,minim:[66,86,96,102,90,24,84,2,103,55,68,88,50,80,4,14,54,70,18],getnumel:16,higher:[23,38,25,37,0,16,40,35,3,11,54,73,30,88,84,70,97,18],x83:108,x87:70,x86:[91,0,73,93,70,6,64,104,5,9,10,52,77,22,80,23,60,29,84,85,86,87,26,115],wherea:[16,84,49,78,107,70],robust:[10,27],wherev:[68,39,16],obit:70,stateless:30,lower:[30,68,0,73,46,70,38,40,54,97,45,2,11,14,15,18,52,102,74,103,21,78,23,84,86,87,88,64,114],n2429:68,machineri:[33,101],discourag:[4,20,16,65],find_packag:60,"try":[30,91,32,68,4,70,37,38,84,40,112,97,45,2
 ,48,11,49,12,13,14,15,16,18,19,53,20,76,78,83,24,61,86,25,107,65,105],searchabl:65,chees:68,propos:[32,29,25,103,58],module_code_asm:111,stripwarnmsg:65,inlinedat:[29,70],islocaltounit:103,succ_end:16,waymark:16,parse_var_init:15,xxxisellow:52,circumv:20,exposit:[43,17,48],getbinarycodeforinstr:52,lmalloc:20,filename1:66,type_code_label:111,finder:37,view_function_cfg_onli:13,complaint:[38,11],vendor:[68,70],erasefrompar:[39,52,41,45,2,47,48,74,16],int32x4_t:78,v64:[70,8],ispoint:32,mypassnam:16,preexist:30,awaken:107,image_sym_class_bit_field:108,pers_fn:70,fbb:52,ptrb:8,llvm_yaml_is_flow_sequence_vector:91,short_wchar:70,xmm10:6,xmm11:6,xmm12:6,xmm13:6,xmm14:6,hatsiz:91,cst_code_wide_integ:111,"1st":103,global:[30,84,0,32,1,68,36,98,70,97,66,7,39,96,8,41,5,43,44,45,2,47,48,11,49,12,15,16,17,50,19,52,102,74,20,38,103,76,21,55,23,107,24,40,86,110,111,90,29],understood:[38,84,11,68],litter:25,unspecifi:[73,33,84,70,8],lowerinvok:30,r221139:29,surpris:[16,38,11,70,32],condition_vari:2
 3,multmp:[39,41,45,2,47,48,12,13,14,15,19],glibc:[23,29,97],image_scn_mem_read:108,prof:58,patchset:23,proc:[23,34,52],n3206:68,setdatalayout:[39,45,2,47,48],assignvirt2stackslot:84,runtimedyld:71,mustquot:91,lhs_val:[12,13,14,15,19],ispointertyp:68,"_unwind_resum":107,testfunc:[12,48],arg_begin:[39,41,45,2,47,48,16],image_file_machine_wcemipsv2:108,registerasmprint:52,runonloop:76,threadid:8,tok_then:[39,45,2,47],runonbasicblock:76,plethora:[23,97,16],branchfold:52,prec:[39,14,15,45,2],artifici:103,operandmap:52,question:[68,32,35,70,37,38,40,54,97,45,47,11,49,99,13,15,16,18,102,103,23,82,29,25,50,65,105],"long":[84,31,1,68,94,3,36,101,4,70,38,104,96,40,41,112,97,10,11,16,19,52,102,74,103,76,22,23,83,24,91,87,25,65],lldb:[26,25,68,103,98],arithmet:[66,30,102,0,41,70,84,45,32,15,16,115,19],fptrunc:70,"__cxa_call_unexpect":107,aliasanalysi:[39,40,45,2,47,48,76,70],files:42,lto_codegen_set_pic_model:90,of_channel:[12,13,14,15,18,19],gcca:95,"0x7fffe3e864f0":24,yrc1:93,delta:61,libclan
 g:29,consist:[68,32,33,1,93,36,4,70,6,66,39,40,41,5,45,2,47,48,12,13,14,15,19,52,102,74,20,103,110,56,107,84,86,25,111,26,65,28,115],caller:[30,97,52,41,32,84,85,2,47,103,76,74,83,78,13,14,70,19],eqtyp:64,cmpnumber:32,parsedefinit:[39,41,54,45,2,47,48],mflop:0,arm64:[23,87],tdrr:80,highlight:[66,23,39,84,21,105,16],worklist:[30,16,32],tooldir:65,icc_val:52,cleargraphattr:16,phieliminationid:84,o32:29,numconst:88,simm13:52,cciftyp:52,pat:[84,6,52],"0x0000000000dc8872":98,sdvalu:[84,52],remove_if:16,registerdescriptor:52,maybeoverridden:32,ecosystem:[26,16],at_decl_fil:103,storeregtostackslot:[84,52],parseprimari:[39,41,54,45,2,47,48,14],domfronti:30,containsfoo:68,ccpromotetotyp:52,meaning:[102,74,16,75,21,73,80,105,70],thedoc:91,ccifcc:52,difil:39,ternari:84,gr1:70,elementtyp:70,gr8:[84,52],spillsiz:52,cmpq:85,pervert:[6,99],tag_structure_typ:103,module_code_globalvar:111,edi:[84,5,6],numfilenam:66,block_begin:[12,13,14,15,19],gmake:[76,23,33,97,87],dispel:102,int8ti:16,edx:[84,6,11
 5],uphold:70,xxxiseldagtodag:52,else_bb:[13,14,15],initializenativetargetasmprint:[39,45,2,47,48],needstub:52,estim:[32,58,0],attributerefer:21,formbit:6,fpformbit:6,mcinst:[84,21],whichev:103,reinterpret:78,emitconstantpool:52,relev:[104,82,101,40,70,84,9,86,47,62,69,25,49,26,13,5],mandelhelp:[14,2],sk_specialsquar:101,"0x0002023":103,maxsiz:68,loop_end_bb:[13,14,15],h_inlined_into_g:79,pleas:[84,31,73,34,86,35,68,69,70,38,8,41,9,10,11,49,16,19,51,52,113,93,23,81,105,82,29,61,40,87,25,26,114,28,115],smaller:[30,68,82,74,16,29,84,25,49,70,33],"_main":[79,108],lcuda:8,cfg:[76,30,84,52,70,1,46,47,10,35,3,32,13,16],memset:[30,70,86],dllvm_binutils_incdir:63,fold:[30,64,52,40,41,16,84,86,48,76,88,49,12,70],investig:[38,11,33],ctor:[68,70,46,97],compat:[30,68,73,93,94,70,37,38,96,8,97,46,10,11,74,20,64,103,22,78,56,80,107,29,84,86,25,88,111,24],pointer_offset:73,memcpyopt:[30,86,40],image_file_machine_i386:108,compar:[30,84,0,31,32,33,69,70,39,40,5,44,45,2,47,10,13,14,15,16,18,102,103,58
 ,107,91,50,54,65,115],mainlin:[25,93],smallconst:88,err_load_bio_str:24,dllvm_enable_doxygen_qt_help:60,result_ptr:73,proj_obj_root:[65,50],finishassembl:74,dllvm_targets_to_build:[60,9],chose:[12,31,48],sexi:[43,17],ocamlbuild_plugin:[12,13,14,15,19],destbitcodelib:65,libltdl:65,sext:[70,49],sse41:5,larger:[7,68,52,70,29,84,64,103,25,22,111,36,16],shader:[104,84,68],n2927:68,nsstring:103,unattend:83,typic:[30,68,93,36,70,71,38,96,40,101,5,10,11,16,50,52,102,74,103,76,110,23,59,60,106,107,24,84,87,88,26,65,27,90],n2928:68,apr:4,appli:[30,84,31,93,94,68,4,70,71,38,96,40,45,2,48,11,49,12,14,15,16,52,102,90,20,75,103,76,22,78,23,83,91,86,87,25,113,28,115],app:[62,68,16],inequ:84,loopcond:[39,45,2,47,13,14,15],api:[68,93,37,39,104,8,41,97,48,12,84,16,19,74,20,21,60,29,40,62,63,25,88,26,27],opcod:[39,101,52,41,70,84,45,2,86,68,54,32,69,14,115,16,6,18,19],transformutil:26,gnuwin32:[35,60],sourcefil:94,emitconstpooladdress:52,fed:84,from:[0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,2
 0,21,22,23,24,25,26,28,29,30,31,32,33,35,36,37,38,39,40,41,112,43,44,45,46,47,48,49,50,66,52,53,55,57,58,59,60,61,62,63,64,65,91,67,69,70,71,73,74,75,76,77,78,79,80,83,84,85,86,87,88,90,68,92,93,94,95,96,97,98,100,101,102,103,104,82,107,109,110,111,54,113,114,115],stream:[68,0,92,5,70,66,7,95,112,12,13,14,84,16,17,18,19,52,75,76,110,23,15,106,91,111,54],ineg:84,few:[30,68,0,93,4,70,38,39,96,8,41,54,2,48,10,11,12,14,16,50,19,52,74,75,103,76,23,83,29,84,86,25,18,111,26,65],muclibc:29,usr:[23,60,8,20,9,87,63,65],regconstraint:84,my_addit:103,sort:[68,70,66,38,54,97,45,47,48,11,12,13,15,16,18,20,103,110,60,61,86,25],clever:[38,11,101],ap2:70,cimag:[14,2],adc64mi8:6,framerecov:70,llvmtooldir:65,tok_identifi:[39,41,54,43,45,2,47,48],is_zero_undef:70,localdynam:[70,111],augment:[14,16,2],lbb0_2:85,corpus_dir:24,annot:[59,8,103,49,27,70],"__clear_cach":70,annoi:68,no_dead_strip:70,endian:[37,111,52,29,84,103,78,70],typesequ:64,getregclass:84,proof:3,cta:8,quickstart:[23,37,33,9,87,10,63,105
 ],tar:[23,31,24,9,93,35,65],isindirectbranch:6,movapd:5,tag:[66,23,68,74,16,91,103,93,21,111,73,65,27,70],proprietari:25,tab:[68,5],xmin:[14,2],tag_apple_properti:103,predicate_stor:52,featurefparmv8:6,six:[84,1,86],getregisteredopt:20,subdirectori:[23,60,52,33,1,87,93,10,26,50],instead:[30,91,32,1,46,94,68,69,4,98,70,66,37,7,101,84,8,41,54,43,97,45,2,48,10,11,49,73,12,14,15,16,17,18,19,52,53,74,20,75,38,76,110,22,80,102,93,23,59,60,106,83,24,40,85,86,25,88,111,26,65,28,29],constantfp:[39,41,45,2,47,48,16,19],dwo:89,chri:[38,68,84,93,76,25,11],sil:6,tension:[15,45],fpext:70,vehicletyp:68,hazard:59,singlethread:70,printdens:[14,2],attent:[10,25,70,52],hasiniti:16,initialize_ag_pass:76,mynewpass:112,light:[29,68,70],llvm_build_exampl:60,freebsd:[23,29,84,93],elid:[74,46,115],elig:30,elim:[77,103],dw_tag_memb:103,getanalysisifavail:76,elis:46,attrparsedattrlist:21,build_fsub:19,projlibsopt:65,reilli:16,initroot:74,"80x87":84,multimap:16,crash:[30,38,23,74,112,24,61,83,88,11,80,16],attr
 pchread:21,nonneg:70,devel:31,createbasictyp:39,nfc:59,trac:113,automak:[23,65],edit:[23,16,60,96],fuzz:24,trap:[70,102],codegenprepar:30,instsp:52,forcibl:70,image_scn_align_8byt:108,clangcommentcommandlist:21,mylistel:91,armneonsema:21,"__chkstk":22,sahf:84,argumentlisttyp:16,const_use_iter:16,frontier:[30,15,45],llvm_compiler_job:60,m_func:16,distnam:65,categori:[30,68,52,16,20,61,103,10,21,70,33],sectalign:20,basic_ss:115,stroustrup:16,llvmbb:37,llvmconfig:60,dive:[43,17,101],proviso:25,ocamlfind:29,powerpc:[23,64,84,60,52,29,91,86,87,88,104,70],bitset1:55,dictionari:[1,70],deadarghax0r:30,promptli:25,my86_64flag:91,image_sym_class_undefined_label:108,tailcalle:84,lto:[59,29,55,63,111,90],isdef:84,mrm1r:52,flaground:91,isfoo:68,"0x2000":103,prioriti:[70,103,102],"0x580be3":24,unknown:[91,0,34,70,39,96,41,54,43,45,2,47,48,12,13,14,15,17,18,19,20,84,63],printoperand:52,boil:[101,2,47,25,78,13,14],misunderstood:[37,97,102],tidbit:[51,38,39,40,43,45,11,15,17],shell:[23,39,60,20,1,10
 ,105,83,97],unabridg:[15,45],juli:74,global_iter:16,protocol:[73,68],emac:[23,68,6,65],probe:[22,84,16],utf:[23,21],clangattrparserstringswitch:21,ssl_new:24,bitcodewrit:[64,16],clip:98,favorit:[13,59,47],cohen:4,linker:[68,67,70,37,8,97,9,2,10,83,100,52,20,103,77,22,23,106,16,29,84,63,26,65,90],appel89:74,peform:78,coher:[26,70],lowerfp_to_sint:52,disjoint:[40,70,0],printvar:65,inform:[30,61,0,31,32,33,1,68,34,67,93,94,35,3,36,69,4,98,70,6,71,37,38,39,104,84,8,41,5,97,9,2,48,10,11,49,45,12,14,15,16,115,50,19,51,102,52,53,74,101,20,75,103,105,76,113,21,22,57,110,23,59,60,106,109,73,107,29,40,87,91,63,25,88,111,112,26,65,27,114,90,66],diverg:[14,2,102],rout:40,"__unwind_info":84,anyregcc:[88,70,111],which:[0,1,2,3,4,5,6,8,9,10,11,12,13,14,15,16,18,19,20,21,23,24,25,26,27,28,29,30,31,32,33,35,36,37,38,39,40,41,112,43,44,45,46,47,48,49,50,66,52,53,103,56,59,60,61,63,65,91,69,70,71,72,73,74,75,76,77,78,80,83,84,85,86,87,88,90,68,93,94,96,97,98,99,100,101,102,64,107,110,111,54,113,105,11
 5],movsx32rm16:84,ncsa:25,llvmtarget:50,clash:[68,70],safepointaddress:74,clase:16,sunwspro:23,image_file_machine_ia64:108,dw_op_addr:103,hassideeffect:6,attributelist:[21,56],dens:[70,16,111],addregfrm:52,pipe:[4,1,5],osuosl:113,determin:[30,61,91,32,33,1,93,69,4,70,71,101,96,8,41,54,2,47,10,13,14,84,16,50,19,66,52,20,75,103,76,77,60,107,40,88,18,111,65],nextindvar:70,const_arg_iter:16,setindexedstoreact:52,"30pm":91,mainloop:[39,41,54,45,2,47,48],filetyp:[35,77],findregress:31,arm_neon:[21,78],liveinterv:[80,84],mistyp:68,strtol:20,locat:[30,61,0,31,73,33,1,67,4,70,71,37,39,84,8,5,97,45,2,10,49,14,15,16,50,66,52,53,74,20,103,79,102,96,23,60,107,29,40,86,87,91,88,65,27],preserve_allcc:[70,111],eatomtypetypeflag:103,multmp4:[12,48],local:[30,91,32,1,68,70,97,71,84,8,41,43,44,45,48,10,73,12,15,16,17,19,74,20,103,76,21,80,110,58,23,59,29,40,87,77,88,111,65,28],multmp1:[41,19],multmp2:[41,19],multmp3:[41,19],contribut:[51,37,16,84,76,25,30,70],pypi:97,succe:[92,7,39,95,96,106,101,112,7
 5,45,100,114,10,77,54,36,113,107,15,5,18],buildtool:26,blarg:16,lto_module_t:90,operating_system:70,dw_tag_user_bas:103,selectcod:52,regalloclinearscan:84,image_rel_i386_sect:22,partit:[30,84,77,83,34],view:[30,33,43,90,29,84,86,47,111,13,16,17],modulo:[84,70,103],knowledg:[66,30,38,68,84,10,25,11,111,65,27,105,70],maketir:68,objectcach:71,dw_form_xxx:103,int16_t:[91,52],p20:8,image_sym_class_enum_tag:108,image_scn_lnk_remov:108,becaus:[30,84,0,32,33,1,46,35,68,69,4,70,6,71,38,39,96,40,41,5,43,97,9,2,47,48,11,49,45,12,13,14,15,16,17,18,19,66,52,102,74,101,20,103,76,110,78,56,93,23,73,83,91,86,87,25,88,54,111,107,65,90,115],gmail:23,closer:[29,59,102],entranc:70,framemap:74,mainli:[32,21,50],divisionbyzero:70,dll:[10,70,111],favor:[33,25],libsystem:68,beginassembl:74,"__apple_nam":103,rppassmanag:76,image_sym_dtype_funct:108,llvm_enable_assert:60,amen:84,clangattrdump:21,sprinkl:16,job:[23,60,101,24,87,76,4],mapopt:91,noalia:[102,70,49,111,40],externallinkag:[39,41,45,2,47,48,19],exc
 lam:70,addit:[30,61,107,0,32,33,1,46,94,35,68,36,4,70,6,66,7,104,84,8,41,5,45,2,48,10,11,49,73,12,14,15,16,18,19,52,102,74,54,20,75,38,103,76,77,22,93,23,59,83,29,40,86,25,88,50,111,112,26,65,27],"0x00000120":103,thenbb:[13,39,45,2,47],constantint:[68,16],tgtm:23,mlimit:112,grain:[29,16],committe:16,libtinfo:9,uint16_t:[69,91,103,52],unclear:[15,45,40],parallel_loop_access:70,wall:[76,38,1,11],hyphen:[20,52],wonder:[68,101,102,97,48,12],arriv:102,chmod:23,walk:[30,32,29,91,76,16],"00myglob":103,respect:[68,73,93,70,6,52,40,112,97,45,15,16,50,101,102,74,79,23,83,84,25,107,27],rpo:59,yaml:[37,91,108],decent:[64,39,34,93,76,16],xxxcallingconv:52,compos:[66,96,103,35,65,70],compon:[30,61,33,93,94,42,71,37,8,70,98,16,50,100,52,53,74,23,59,60,24,84,25,88,26,65],packedvector:16,besid:[68,52,54,20,2,10,14,70,18],inbound:[66,70,49,102],presenc:[52,5,29,84,86,70,107,16,33],gtx:8,ptxa:8,present:[84,32,1,70,37,39,5,45,2,47,13,14,15,16,102,74,20,103,79,80,23,29,61,111,65,28],xorrr:52,align:[66,3
 0,84,104,111,52,8,74,32,91,103,5,86,90,88,49,78,56,102,70],dfpregsclass:52,constprop:[30,20,16],wili:102,wild:[14,20,2],xorri:52,bb3:70,bb2:[70,111],bb1:[70,111],d_ctor_bas:5,layer:[38,84,11,40],avx:[10,0],instrinfo:[84,21,52],cctype:[39,41,54,45,2,47,48],eptr:70,avl:16,motiv:[29,45,47,88,69,13,15],dual:25,add64mi32:6,dinstinguish:103,incq:5,getattributespellinglistindex:21,uint16x4_t:78,gprof:[23,87,65],xxxschedul:52,cross:[23,60,37,32,9,34,87,70,112,16],member:[71,30,64,84,96,52,0,101,16,29,91,68,103,55,10,90,102,70,33,115],binary_preced:[14,15],clangsharp:29,largest:[70,84,22,49],linaro:34,f64:[84,70,52,8],expcnt:72,"0x1b":111,hasjit:52,sopp:72,maptag:91,ssecal:52,hardcodedsmalls:16,bcpl:28,usecas:29,decoupl:115,outputtyp:64,underneath:[10,23,87,50],extra_dist:65,inc4:5,minsizerel:60,"0x11":103,"0x10":[88,103],linkagetyp:16,getrawpoint:56,my_function_fast:8,machinefunct:[76,84,16],libdevic:8,getoffset:52,camel:68,converg:[14,2],obtain:[71,30,84,52,61,25,65,4,115,16,6,66],corei7:[
 10,0],heavili:[74,37,38,97,11],tce:29,tcb:85,expr1rh:66,now:[84,32,33,1,46,68,70,37,38,39,96,8,41,5,97,9,2,47,48,11,45,12,13,14,15,16,18,19,101,74,20,64,103,76,93,23,81,60,82,83,29,91,86,25,88,54,24],methodproto:52,amd64:23,eatomtypenul:103,smith:68,book:[76,37,68,59,16],waypoint:83,emitobject:71,smart:68,llvm_on_win32:4,llvmdisassembler_option_usemarkup:27,agnost:[4,84,103,78],strconcat:[28,52,115],lightweight:[68,1,16],know:[30,91,0,32,33,1,35,68,98,70,66,38,39,84,40,41,54,97,45,2,47,48,10,11,49,73,12,13,14,15,16,18,19,52,74,20,103,76,78,23,60,82,83,24,61,86,25,113,105,90],nor:[30,68,102,74,32,84,35,88,111,65,4,70,97],librarynam:[74,65,76,52,50],"7e15":20,hostc:8,hostb:8,hosta:8,incred:[25,68],repurpos:103,unord:[105,70,86,52],"0xff":115,createphi:[39,45,2,47],unabbrev_record:111,growth:[70,84,16],"export":[23,60,40,90,20,84,2,93,63,65,70],superclass:[52,40,76,16,6,115],package_vers:60,add64ri32:6,not_found:[12,13,14,15,18,19],leaf:[107,103],image_sym_class_struct_tag:108,lead:[30
 ,39,102,16,20,91,86,63,68,54,65,84,70,24,18,115],sjlj:107,leak:[43,74,29,1,85,46,10,17],leaq:85,leav:[30,61,82,52,23,74,32,20,1,103,63,8,70,97],prehead:[13,47,30],leader:68,getnam:[39,41,103,97,45,2,47,48,76,16],numstr:[39,41,54,43,45,2,47,48],acronym:37,"enum":[68,69,70,6,64,39,101,40,41,54,43,45,2,47,48,84,16,52,74,20,103,21,56,91,108,114],tdfile:65,xxxgencallingconv:52,obei:[29,70],eatomtypenameflag:103,rare:[68,111,52,74,5,84,49,70,107,16,115],add64mi8:6,column:[66,23,39,0,29,103,68,69,70,33],type_code_doubl:111,lppassmanag:76,constructor:[71,84,101,52,16,20,91,46,47,86,76,68,56,70,97],spiller:[80,77,84],disabl:[68,0,31,1,93,5,39,40,70,97,9,47,13,16,74,20,75,77,78,80,23,60,83,61,87,62,63,112,65],stackentri:74,desrib:66,own:[30,68,33,93,4,70,71,38,101,43,97,45,2,10,11,49,14,15,16,17,50,66,52,74,20,64,103,76,21,58,23,81,60,82,24,84,63,25,88,111,26,65,29],automat:[30,84,32,1,67,68,70,37,101,40,41,112,97,9,46,47,48,12,13,16,50,19,52,74,20,103,76,113,21,23,60,82,83,29,91,85,77,26,65,
 105,115],warranti:[76,25],dbuilder:39,build_mod:35,val:[39,52,8,41,16,20,45,2,47,48,68,88,54,111,56,70,115],transfer:[85,70,46,78,107],threadsanit:70,intention:[76,54,68,70,18],appl:[37,5,84,103,98,25,70],arg1:[43,70,17],"var":[39,8,32,45,103,15,70,115],incorr:3,varexpr:[15,45,39],mailer:25,"0x7fffffff":70,codegen_expr:[12,13,14,15,19],lazyresolverfn:52,made:[30,84,32,93,68,70,6,37,38,39,40,41,97,45,2,47,48,11,99,13,15,16,50,101,102,103,76,21,78,107,91,85,25,111,65,105],temp:[29,61],whether:[30,84,32,68,70,38,96,40,101,54,45,2,47,11,73,13,14,15,16,50,52,102,74,20,75,64,55,21,80,58,23,60,82,83,24,61,63,77,88,18,111,107,26,90,115],troubl:[23,20,25,35],record:[66,38,25,82,28,33,75,77,88,21,11,111,73,80,110,114,70,6,115],below:[30,84,0,31,32,33,34,46,35,68,70,66,7,96,8,101,5,45,2,10,72,73,12,14,15,16,18,52,20,103,76,21,93,23,60,77,40,85,87,25,88,50,111,54,26,65],structtyp:16,ptrreg:84,lvm:39,targetdescript:52,llvmasmpars:[64,50],numberexpr:[39,41,54,45,2,47,48,12,13,14,15,18,19],signifi
 cantli:[68,70,47,76,90,54,111,36,13,16,18],entiteti:73,link_libs_in_shar:65,meaningless:73,rl5:8,create_entry_block_alloca:15,"8bit":24,sparseset:16,rl7:8,mutual:[41,20,43,17,19],targetfunc:16,immateri:32,the_modul:[12,13,14,15,19],percent:40,constantfold:64,parsecommandlineopt:20,other:[0,1,2,3,4,5,6,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26,28,29,30,31,32,33,34,35,37,38,39,40,41,54,43,44,45,46,47,48,49,50,51,52,103,56,58,59,60,61,63,65,66,91,69,70,71,73,74,75,76,77,78,79,83,84,86,87,89,90,68,93,94,104,96,97,99,101,102,64,105,82,107,110,111,114,115],bool:[84,32,68,64,39,101,40,41,45,2,47,48,12,13,14,15,16,19,52,74,20,103,76,60,91],branch:[30,68,93,94,3,70,37,39,104,97,45,2,47,49,13,14,15,16,52,74,58,23,82,107,29,84,25],gline:0,neelakantam:30,inst_iter:16,keep_symbol:65,junk:[12,13,14,15,18,19],xxxsubtarget:52,indexedmap:[84,16],clangcommentcommandinfo:21,add_subdirectori:60,tok_extern:[39,41,54,43,45,2,47,48],debian:[62,23,9],stringmap:[20,16,8],experienc:83,sass:8,rel
 iabl:[84,1,60],subregclasslist:52,pdata:22,emerg:98,auxiliari:52,invari:[30,59,40,73,16,76,49,23,70],istermin:[6,115]},objtypes:{"0":"std:option"},titles:["Auto-Vectorization in LLVM","lit - LLVM Integrated Tester","6. Kaleidoscope: Extending the Language: User-defined Operators","LLVM Branch Weight Metadata","System Library","FileCheck - Flexible pattern matching file verifier","TableGen","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","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 AS
 T","3. Kaleidoscope: Code generation to LLVM IR","CommandLine 2.0 Library Manual","TableGen BackEnds","LLVM Extensions","Getting Started with the LLVM System","LibFuzzer – a library for coverage-guided fuzz testing.","LLVM Developer Policy","LLVMBuild Guide","LLVM’s Optional Rich Disassembly Output","TableGen Language Reference","LLVM 3.6 Release Notes","LLVM’s Analysis and Transform Passes","How To Validate a New Release","MergeFunctions pass, how it works","LLVM test-suite Makefile Guide","How To Build On ARM","Getting Started with the LLVM System using Microsoft Visual Studio","llvm-bcanalyzer - LLVM bitcode analyzer","Overview","9. Kaleidoscope: Conclusion and other useful LLVM tidbits","8. Kaleidoscope: Extending the Language: Debug Information","LLVM Alias Analysis Infrastructure","3. Kaleidoscope: Code generation to LLVM IR","llvm-stress - generate random .ll files","1. Kaleidoscope: Tutorial Introduction and the Lexer","llvm-diff - LLVM structural ‘di
 ff’","7. Kaleidoscope: Extending the Language: Mutable Variables","Design and Usage of the InAlloca Attribute","5. Kaleidoscope: Extending the Language: Control Flow","4. Kaleidoscope: Adding JIT and Optimizer Support","Performance Tips for Frontend Authors","Creating an LLVM Project","LLVM Tutorial: Table of Contents","Writing an LLVM Backend","llvm-build - LLVM Project Build Utility","2. Kaleidoscope: Implementing a Parser and AST","Bitsets","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 Packaging LLVM","The LLVM gold plugin","Extending LLVM: Adding instructions, intrinsics, types, etc.","LLVM Makefile Guide","LLVM Code Coverage Mapping Format","LLVM Command Guide","LLVM Coding Standards","How To Use Instruction Mappings","LLVM Language Reference Manual","MCJIT Design and Implementation","User Guide for R600 Back-end","Garbage Collection
  Safepoints in LLVM","Accurate Garbage Collection with LLVM","opt - LLVM optimizer","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","Code Reviews with Phabricator","LLVM bugpoint tool: design and usage","The LLVM Target-Independent Code Generator","Segmented Stacks in LLVM","LLVM Atomic Instructions and Concurrency Guide","Building LLVM With Autotools","Stack maps and patch points in LLVM","llvm-dwarfdump - print contents of DWARF sections","LLVM Link Time Optimization: Design and Implementation","YAML I/O","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","llvm-config - Print LLVM compilation o
 ptions","How to set up LLVM-style RTTI for your class hierarchy","The Often Misunderstood GEP Instruction","Source Level Debugging with LLVM","Architecture & Platform Information for Compiler Writers","Sphinx Quickstart Template","llvm-link - LLVM bitcode linker","Exception Handling in LLVM","yaml2obj","llvm-profdata - Profile data tool","llvm-nm - list LLVM bitcode and object file’s symbol table","LLVM Bitcode File Format","bugpoint - automatic test case reduction tool","How To Add Your Build Configuration To LLVM Buildbot Infrastructure","tblgen - Target Description To C++ Code Generator","TableGen Language Introduction"],objnames:{"0":["std","option","option"]},filenames:["Vectorizers","CommandGuide/lit","tutorial/LangImpl6","BranchWeightMetadata","SystemLibrary","CommandGuide/FileCheck","TableGen/index","CommandGuide/llvm-extract","NVPTXUsage","HowToCrossCompileLLVM","TestingGuide","tutorial/OCamlLangImpl8","tutorial/OCamlLangImpl4","tutorial/OCamlLangImpl5","tutorial/
 OCamlLangImpl6","tutorial/OCamlLangImpl7","ProgrammersManual","tutorial/OCamlLangImpl1","tutorial/OCamlLangImpl2","tutorial/OCamlLangImpl3","CommandLine","TableGen/BackEnds","Extensions","GettingStarted","LibFuzzer","DeveloperPolicy","LLVMBuild","MarkedUpDisassembly","TableGen/LangRef","ReleaseNotes","Passes","ReleaseProcess","MergeFunctions","TestSuiteMakefileGuide","HowToBuildOnARM","GettingStartedVS","CommandGuide/llvm-bcanalyzer","index","tutorial/LangImpl9","tutorial/LangImpl8","AliasAnalysis","tutorial/LangImpl3","CommandGuide/llvm-stress","tutorial/LangImpl1","CommandGuide/llvm-diff","tutorial/LangImpl7","InAlloca","tutorial/LangImpl5","tutorial/LangImpl4","Frontend/PerformanceTips","Projects","tutorial/index","WritingAnLLVMBackend","CommandGuide/llvm-build","tutorial/LangImpl2","BitSets","HowToUseAttributes","CommandGuide/llvm-readobj","BlockFrequencyTerminology","Lexicon","CMake","HowToSubmitABug","Packaging","GoldPlugin","ExtendingLLVM","MakefileGuide","CoverageMappingForm
 at","CommandGuide/index","CodingStandards","HowToUseInstrMappings","LangRef","MCJITDesignAndImplementation","R600Usage","Statepoints","GarbageCollection","CommandGuide/opt","WritingAnLLVMPass","CommandGuide/llc","BigEndianNEON","CommandGuide/llvm-symbolizer","CommandGuide/lli","TableGenFundamentals","Phabricator","Bugpoint","CodeGenerator","SegmentedStacks","Atomics","BuildingLLVMWithAutotools","StackMaps","CommandGuide/llvm-dwarfdump","LinkTimeOptimization","YamlIO","CommandGuide/llvm-dis","HowToReleaseLLVM","CommandGuide/llvm-cov","CommandGuide/llvm-as","CommandGuide/llvm-ar","FAQ","DebuggingJITedCode","TableGen/Deficiencies","CommandGuide/llvm-config","HowToSetUpLLVMStyleRTTI","GetElementPtr","SourceLevelDebugging","CompilerWriterInfo","SphinxQuickstartTemplate","CommandGuide/llvm-link","ExceptionHandling","yaml2obj","CommandGuide/llvm-profdata","CommandGuide/llvm-nm","BitCodeFormat","CommandGuide/bugpoint","HowToAddABuilder","CommandGuide/tblgen","TableGen/LangIntro"]})
\ No newline at end of file

Added: www-releases/trunk/3.6.1/docs/tutorial/LangImpl1.html
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/tutorial/LangImpl1.html?rev=238135&view=auto
==============================================================================
--- www-releases/trunk/3.6.1/docs/tutorial/LangImpl1.html (added)
+++ www-releases/trunk/3.6.1/docs/tutorial/LangImpl1.html Mon May 25 08:53:02 2015
@@ -0,0 +1,350 @@
+
+
+<!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.6 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.6',
+        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.6 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="LangImpl2.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="LangImpl2.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 leaks memory, 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="LangImpl2.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="LangImpl3.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="LangImpl4.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="LangImpl5.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="LangImpl6.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="LangImpl7.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="LangImpl8.html">Chapter #8</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 700 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"><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>
+<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"><pre>extern sin(arg);
+extern cos(arg);
+extern atan2(arg1 arg2);
+
+atan2(sin(.4), cos(42))</pre>
+</div>
+<p>A more interesting example is included in Chapter 6 where we write a
+little Kaleidoscope application that <a class="reference external" href="LangImpl6.html#example">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="LangImpl2.html#code">full code listing</a> for the Lexer
+is available in the <a class="reference external" href="LangImpl2.html">next chapter</a> of the tutorial).
+Next we’ll <a class="reference external" href="LangImpl2.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="LangImpl2.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="LangImpl2.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-2014, LLVM Project.
+      Last updated on 2015-05-25.
+      Created using <a href="http://sphinx.pocoo.org/">Sphinx</a> 1.1.3.
+    </div>
+  </body>
+</html>
\ No newline at end of file

Added: www-releases/trunk/3.6.1/docs/tutorial/LangImpl2.html
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/tutorial/LangImpl2.html?rev=238135&view=auto
==============================================================================
--- www-releases/trunk/3.6.1/docs/tutorial/LangImpl2.html (added)
+++ www-releases/trunk/3.6.1/docs/tutorial/LangImpl2.html Mon May 25 08:53:02 2015
@@ -0,0 +1,1117 @@
+
+
+<!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. Kaleidoscope: Implementing a Parser and AST — LLVM 3.6 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.6',
+        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.6 documentation" href="../index.html" />
+    <link rel="up" title="LLVM Tutorial: Table of Contents" href="index.html" />
+    <link rel="next" title="3. Kaleidoscope: Code generation to LLVM IR" href="LangImpl3.html" />
+    <link rel="prev" title="1. Kaleidoscope: Tutorial Introduction and the Lexer" href="LangImpl1.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="LangImpl3.html" title="3. Kaleidoscope: Code generation to LLVM IR"
+             accesskey="N">next</a> |</li>
+        <li class="right" >
+          <a href="LangImpl1.html" title="1. Kaleidoscope: Tutorial Introduction and the Lexer"
+             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-implementing-a-parser-and-ast">
+<h1>2. Kaleidoscope: Implementing a Parser and AST<a class="headerlink" href="#kaleidoscope-implementing-a-parser-and-ast" 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="id2">Chapter 2 Introduction</a></li>
+<li><a class="reference internal" href="#the-abstract-syntax-tree-ast" id="id3">The Abstract Syntax Tree (AST)</a></li>
+<li><a class="reference internal" href="#parser-basics" id="id4">Parser Basics</a></li>
+<li><a class="reference internal" href="#basic-expression-parsing" id="id5">Basic Expression Parsing</a></li>
+<li><a class="reference internal" href="#binary-expression-parsing" id="id6">Binary Expression Parsing</a></li>
+<li><a class="reference internal" href="#parsing-the-rest" id="id7">Parsing the Rest</a></li>
+<li><a class="reference internal" href="#the-driver" id="id8">The Driver</a></li>
+<li><a class="reference internal" href="#conclusions" id="id9">Conclusions</a></li>
+<li><a class="reference internal" href="#full-code-listing" id="id10">Full Code Listing</a></li>
+</ul>
+</div>
+<div class="section" id="chapter-2-introduction">
+<h2><a class="toc-backref" href="#id2">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 “<a class="reference external" href="index.html">Implementing a language with
+LLVM</a>” tutorial. This chapter shows you how to use the
+lexer, built in <a class="reference external" href="LangImpl1.html">Chapter 1</a>, to build a full
+<a class="reference external" href="http://en.wikipedia.org/wiki/Parsing">parser</a> for our Kaleidoscope
+language. Once we have a parser, we’ll define and build an <a class="reference external" href="http://en.wikipedia.org/wiki/Abstract_syntax_tree">Abstract
+Syntax Tree</a> (AST).</p>
+<p>The parser we will build uses a combination of <a class="reference external" href="http://en.wikipedia.org/wiki/Recursive_descent_parser">Recursive Descent
+Parsing</a> and
+<a class="reference external" href="http://en.wikipedia.org/wiki/Operator-precedence_parser">Operator-Precedence
+Parsing</a> to
+parse the Kaleidoscope language (the latter for binary expressions and
+the former for everything else). Before we get to parsing though, lets
+talk about the output of the parser: the Abstract Syntax Tree.</p>
+</div>
+<div class="section" id="the-abstract-syntax-tree-ast">
+<h2><a class="toc-backref" href="#id3">2.2. The Abstract Syntax Tree (AST)</a><a class="headerlink" href="#the-abstract-syntax-tree-ast" title="Permalink to this headline">¶</a></h2>
+<p>The AST for a program captures its behavior in such a way that it is
+easy for later stages of the compiler (e.g. code generation) to
+interpret. We basically want one object for each construct in the
+language, and the AST should closely model the language. In
+Kaleidoscope, we have expressions, a prototype, and a function object.
+We’ll start with expressions first:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">/// ExprAST - Base class for all expression nodes.</span>
+<span class="k">class</span> <span class="nc">ExprAST</span> <span class="p">{</span>
+<span class="nl">public:</span>
+  <span class="k">virtual</span> <span class="o">~</span><span class="n">ExprAST</span><span class="p">()</span> <span class="p">{}</span>
+<span class="p">};</span>
+
+<span class="c1">/// NumberExprAST - Expression class for numeric literals like "1.0".</span>
+<span class="k">class</span> <span class="nc">NumberExprAST</span> <span class="o">:</span> <span class="k">public</span> <span class="n">ExprAST</span> <span class="p">{</span>
+  <span class="kt">double</span> <span class="n">Val</span><span class="p">;</span>
+<span class="nl">public:</span>
+  <span class="n">NumberExprAST</span><span class="p">(</span><span class="kt">double</span> <span class="n">val</span><span class="p">)</span> <span class="o">:</span> <span class="n">Val</span><span class="p">(</span><span class="n">val</span><span class="p">)</span> <span class="p">{}</span>
+<span class="p">};</span>
+</pre></div>
+</div>
+<p>The code above shows the definition of the base ExprAST class and one
+subclass which we use for numeric literals. The important thing to note
+about this code is that the NumberExprAST class captures the numeric
+value of the literal as an instance variable. This allows later phases
+of the compiler to know what the stored numeric value is.</p>
+<p>Right now we only create the AST, so there are no useful accessor
+methods on them. It would be very easy to add a virtual method to pretty
+print the code, for example. Here are the other expression AST node
+definitions that we’ll use in the basic form of the Kaleidoscope
+language:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">/// VariableExprAST - Expression class for referencing a variable, like "a".</span>
+<span class="k">class</span> <span class="nc">VariableExprAST</span> <span class="o">:</span> <span class="k">public</span> <span class="n">ExprAST</span> <span class="p">{</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="nl">public:</span>
+  <span class="n">VariableExprAST</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="o">:</span> <span class="n">Name</span><span class="p">(</span><span class="n">name</span><span class="p">)</span> <span class="p">{}</span>
+<span class="p">};</span>
+
+<span class="c1">/// BinaryExprAST - Expression class for a binary operator.</span>
+<span class="k">class</span> <span class="nc">BinaryExprAST</span> <span class="o">:</span> <span class="k">public</span> <span class="n">ExprAST</span> <span class="p">{</span>
+  <span class="kt">char</span> <span class="n">Op</span><span class="p">;</span>
+  <span class="n">ExprAST</span> <span class="o">*</span><span class="n">LHS</span><span class="p">,</span> <span class="o">*</span><span class="n">RHS</span><span class="p">;</span>
+<span class="nl">public:</span>
+  <span class="n">BinaryExprAST</span><span class="p">(</span><span class="kt">char</span> <span class="n">op</span><span class="p">,</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="n">lhs</span><span class="p">,</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="n">rhs</span><span class="p">)</span>
+    <span class="o">:</span> <span class="n">Op</span><span class="p">(</span><span class="n">op</span><span class="p">),</span> <span class="n">LHS</span><span class="p">(</span><span class="n">lhs</span><span class="p">),</span> <span class="n">RHS</span><span class="p">(</span><span class="n">rhs</span><span class="p">)</span> <span class="p">{}</span>
+<span class="p">};</span>
+
+<span class="c1">/// CallExprAST - Expression class for function calls.</span>
+<span class="k">class</span> <span class="nc">CallExprAST</span> <span class="o">:</span> <span class="k">public</span> <span class="n">ExprAST</span> <span class="p">{</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="n">Callee</span><span class="p">;</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">vector</span><span class="o"><</span><span class="n">ExprAST</span><span class="o">*></span> <span class="n">Args</span><span class="p">;</span>
+<span class="nl">public:</span>
+  <span class="n">CallExprAST</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">callee</span><span class="p">,</span> <span class="n">std</span><span class="o">::</span><span class="n">vector</span><span class="o"><</span><span class="n">ExprAST</span><span class="o">*></span> <span class="o">&</span><span class="n">args</span><span class="p">)</span>
+    <span class="o">:</span> <span class="n">Callee</span><span class="p">(</span><span class="n">callee</span><span class="p">),</span> <span class="n">Args</span><span class="p">(</span><span class="n">args</span><span class="p">)</span> <span class="p">{}</span>
+<span class="p">};</span>
+</pre></div>
+</div>
+<p>This is all (intentionally) rather straight-forward: variables capture
+the variable name, binary operators capture their opcode (e.g. ‘+’), and
+calls capture a function name as well as a list of any argument
+expressions. One thing that is nice about our AST is that it captures
+the language features without talking about the syntax of the language.
+Note that there is no discussion about precedence of binary operators,
+lexical structure, etc.</p>
+<p>For our basic language, these are all of the expression nodes we’ll
+define. Because it doesn’t have conditional control flow, it isn’t
+Turing-complete; we’ll fix that in a later installment. The two things
+we need next are a way to talk about the interface to a function, and a
+way to talk about functions themselves:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">/// PrototypeAST - This class represents the "prototype" for a function,</span>
+<span class="c1">/// which captures its name, and its argument names (thus implicitly the number</span>
+<span class="c1">/// of arguments the function takes).</span>
+<span class="k">class</span> <span class="nc">PrototypeAST</span> <span class="p">{</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="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">string</span><span class="o">></span> <span class="n">Args</span><span class="p">;</span>
+<span class="nl">public:</span>
+  <span class="n">PrototypeAST</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="k">const</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">string</span><span class="o">></span> <span class="o">&</span><span class="n">args</span><span class="p">)</span>
+    <span class="o">:</span> <span class="n">Name</span><span class="p">(</span><span class="n">name</span><span class="p">),</span> <span class="n">Args</span><span class="p">(</span><span class="n">args</span><span class="p">)</span> <span class="p">{}</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">PrototypeAST</span> <span class="o">*</span><span class="n">Proto</span><span class="p">;</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">PrototypeAST</span> <span class="o">*</span><span class="n">proto</span><span class="p">,</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">proto</span><span class="p">),</span> <span class="n">Body</span><span class="p">(</span><span class="n">body</span><span class="p">)</span> <span class="p">{}</span>
+<span class="p">};</span>
+</pre></div>
+</div>
+<p>In Kaleidoscope, functions are typed with just a count of their
+arguments. Since all values are double precision floating point, the
+type of each argument doesn’t need to be stored anywhere. In a more
+aggressive and realistic language, the “ExprAST” class would probably
+have a type field.</p>
+<p>With this scaffolding, we can now talk about parsing expressions and
+function bodies in Kaleidoscope.</p>
+</div>
+<div class="section" id="parser-basics">
+<h2><a class="toc-backref" href="#id4">2.3. Parser Basics</a><a class="headerlink" href="#parser-basics" title="Permalink to this headline">¶</a></h2>
+<p>Now that we have an AST to build, we need to define the parser code to
+build it. The idea here is that we want to parse something like “x+y”
+(which is returned as three tokens by the lexer) into an AST that could
+be generated with calls like this:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="n">ExprAST</span> <span class="o">*</span><span class="n">X</span> <span class="o">=</span> <span class="k">new</span> <span class="n">VariableExprAST</span><span class="p">(</span><span class="s">"x"</span><span class="p">);</span>
+<span class="n">ExprAST</span> <span class="o">*</span><span class="n">Y</span> <span class="o">=</span> <span class="k">new</span> <span class="n">VariableExprAST</span><span class="p">(</span><span class="s">"y"</span><span class="p">);</span>
+<span class="n">ExprAST</span> <span class="o">*</span><span class="n">Result</span> <span class="o">=</span> <span class="k">new</span> <span class="n">BinaryExprAST</span><span class="p">(</span><span class="sc">'+'</span><span class="p">,</span> <span class="n">X</span><span class="p">,</span> <span class="n">Y</span><span class="p">);</span>
+</pre></div>
+</div>
+<p>In order to do this, we’ll start by defining some basic helper routines:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">/// CurTok/getNextToken - Provide a simple token buffer.  CurTok is the current</span>
+<span class="c1">/// token the parser is looking at.  getNextToken reads another token from the</span>
+<span class="c1">/// lexer and updates CurTok with its results.</span>
+<span class="k">static</span> <span class="kt">int</span> <span class="n">CurTok</span><span class="p">;</span>
+<span class="k">static</span> <span class="kt">int</span> <span class="nf">getNextToken</span><span class="p">()</span> <span class="p">{</span>
+  <span class="k">return</span> <span class="n">CurTok</span> <span class="o">=</span> <span class="n">gettok</span><span class="p">();</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>This implements a simple token buffer around the lexer. This allows us
+to look one token ahead at what the lexer is returning. Every function
+in our parser will assume that CurTok is the current token that needs to
+be parsed.</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">/// Error* - These are little helper functions for error handling.</span>
+<span class="n">ExprAST</span> <span class="o">*</span><span class="nf">Error</span><span class="p">(</span><span class="k">const</span> <span class="kt">char</span> <span class="o">*</span><span class="n">Str</span><span class="p">)</span> <span class="p">{</span> <span class="n">fprintf</span><span class="p">(</span><span class="n">stderr</span><span class="p">,</span> <span class="s">"Error: %s</span><span class="se">\n</span><span class="s">"</span><span class="p">,</span> <span class="n">Str</span><span class="p">);</span><span class="k">return</span> <span class="mi">0</span><span class="p">;}</span>
+<span class="n">PrototypeAST</span> <span class="o">*</span><span class="nf">ErrorP</span><span class="p">(</span><span class="k">const</span> <span class="kt">char</span> <span class="o">*</span><span class="n">Str</span><span class="p">)</span> <span class="p">{</span> <span class="n">Error</span><span class="p">(</span><span class="n">Str</span><span class="p">);</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span> <span class="p">}</span>
+<span class="n">FunctionAST</span> <span class="o">*</span><span class="nf">ErrorF</span><span class="p">(</span><span class="k">const</span> <span class="kt">char</span> <span class="o">*</span><span class="n">Str</span><span class="p">)</span> <span class="p">{</span> <span class="n">Error</span><span class="p">(</span><span class="n">Str</span><span class="p">);</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span> <span class="p">}</span>
+</pre></div>
+</div>
+<p>The <tt class="docutils literal"><span class="pre">Error</span></tt> routines are simple helper routines that our parser will
+use to handle errors. The error recovery in our parser will not be the
+best and is not particular user-friendly, but it will be enough for our
+tutorial. These routines make it easier to handle errors in routines
+that have various return types: they always return null.</p>
+<p>With these basic helper functions, we can implement the first piece of
+our grammar: numeric literals.</p>
+</div>
+<div class="section" id="basic-expression-parsing">
+<h2><a class="toc-backref" href="#id5">2.4. Basic Expression Parsing</a><a class="headerlink" href="#basic-expression-parsing" title="Permalink to this headline">¶</a></h2>
+<p>We start with numeric literals, because they are the simplest to
+process. For each production in our grammar, we’ll define a function
+which parses that production. For numeric literals, we have:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">/// numberexpr ::= number</span>
+<span class="k">static</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="nf">ParseNumberExpr</span><span class="p">()</span> <span class="p">{</span>
+  <span class="n">ExprAST</span> <span class="o">*</span><span class="n">Result</span> <span class="o">=</span> <span class="k">new</span> <span class="n">NumberExprAST</span><span class="p">(</span><span class="n">NumVal</span><span class="p">);</span>
+  <span class="n">getNextToken</span><span class="p">();</span> <span class="c1">// consume the number</span>
+  <span class="k">return</span> <span class="n">Result</span><span class="p">;</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>This routine is very simple: it expects to be called when the current
+token is a <tt class="docutils literal"><span class="pre">tok_number</span></tt> token. It takes the current number value,
+creates a <tt class="docutils literal"><span class="pre">NumberExprAST</span></tt> node, advances the lexer to the next token,
+and finally returns.</p>
+<p>There are some interesting aspects to this. The most important one is
+that this routine eats all of the tokens that correspond to the
+production and returns the lexer buffer with the next token (which is
+not part of the grammar production) ready to go. This is a fairly
+standard way to go for recursive descent parsers. For a better example,
+the parenthesis operator is defined like this:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">/// parenexpr ::= '(' expression ')'</span>
+<span class="k">static</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="nf">ParseParenExpr</span><span class="p">()</span> <span class="p">{</span>
+  <span class="n">getNextToken</span><span class="p">();</span>  <span class="c1">// eat (.</span>
+  <span class="n">ExprAST</span> <span class="o">*</span><span class="n">V</span> <span class="o">=</span> <span class="n">ParseExpression</span><span class="p">();</span>
+  <span class="k">if</span> <span class="p">(</span><span class="o">!</span><span class="n">V</span><span class="p">)</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+
+  <span class="k">if</span> <span class="p">(</span><span class="n">CurTok</span> <span class="o">!=</span> <span class="sc">')'</span><span class="p">)</span>
+    <span class="k">return</span> <span class="n">Error</span><span class="p">(</span><span class="s">"expected ')'"</span><span class="p">);</span>
+  <span class="n">getNextToken</span><span class="p">();</span>  <span class="c1">// eat ).</span>
+  <span class="k">return</span> <span class="n">V</span><span class="p">;</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>This function illustrates a number of interesting things about the
+parser:</p>
+<p>1) It shows how we use the Error routines. When called, this function
+expects that the current token is a ‘(‘ token, but after parsing the
+subexpression, it is possible that there is no ‘)’ waiting. For example,
+if the user types in “(4 x” instead of “(4)”, the parser should emit an
+error. Because errors can occur, the parser needs a way to indicate that
+they happened: in our parser, we return null on an error.</p>
+<p>2) Another interesting aspect of this function is that it uses recursion
+by calling <tt class="docutils literal"><span class="pre">ParseExpression</span></tt> (we will soon see that
+<tt class="docutils literal"><span class="pre">ParseExpression</span></tt> can call <tt class="docutils literal"><span class="pre">ParseParenExpr</span></tt>). This is powerful
+because it allows us to handle recursive grammars, and keeps each
+production very simple. Note that parentheses do not cause construction
+of AST nodes themselves. While we could do it this way, the most
+important role of parentheses are to guide the parser and provide
+grouping. Once the parser constructs the AST, parentheses are not
+needed.</p>
+<p>The next simple production is for handling variable references and
+function calls:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">/// identifierexpr</span>
+<span class="c1">///   ::= identifier</span>
+<span class="c1">///   ::= identifier '(' expression* ')'</span>
+<span class="k">static</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="nf">ParseIdentifierExpr</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">IdName</span> <span class="o">=</span> <span class="n">IdentifierStr</span><span class="p">;</span>
+
+  <span class="n">getNextToken</span><span class="p">();</span>  <span class="c1">// eat identifier.</span>
+
+  <span class="k">if</span> <span class="p">(</span><span class="n">CurTok</span> <span class="o">!=</span> <span class="sc">'('</span><span class="p">)</span> <span class="c1">// Simple variable ref.</span>
+    <span class="k">return</span> <span class="k">new</span> <span class="n">VariableExprAST</span><span class="p">(</span><span class="n">IdName</span><span class="p">);</span>
+
+  <span class="c1">// Call.</span>
+  <span class="n">getNextToken</span><span class="p">();</span>  <span class="c1">// eat (</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">vector</span><span class="o"><</span><span class="n">ExprAST</span><span class="o">*></span> <span class="n">Args</span><span class="p">;</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">CurTok</span> <span class="o">!=</span> <span class="sc">')'</span><span class="p">)</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">ExprAST</span> <span class="o">*</span><span class="n">Arg</span> <span class="o">=</span> <span class="n">ParseExpression</span><span class="p">();</span>
+      <span class="k">if</span> <span class="p">(</span><span class="o">!</span><span class="n">Arg</span><span class="p">)</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+      <span class="n">Args</span><span class="p">.</span><span class="n">push_back</span><span class="p">(</span><span class="n">Arg</span><span class="p">);</span>
+
+      <span class="k">if</span> <span class="p">(</span><span class="n">CurTok</span> <span class="o">==</span> <span class="sc">')'</span><span class="p">)</span> <span class="k">break</span><span class="p">;</span>
+
+      <span class="k">if</span> <span class="p">(</span><span class="n">CurTok</span> <span class="o">!=</span> <span class="sc">','</span><span class="p">)</span>
+        <span class="k">return</span> <span class="n">Error</span><span class="p">(</span><span class="s">"Expected ')' or ',' in argument list"</span><span class="p">);</span>
+      <span class="n">getNextToken</span><span class="p">();</span>
+    <span class="p">}</span>
+  <span class="p">}</span>
+
+  <span class="c1">// Eat the ')'.</span>
+  <span class="n">getNextToken</span><span class="p">();</span>
+
+  <span class="k">return</span> <span class="k">new</span> <span class="n">CallExprAST</span><span class="p">(</span><span class="n">IdName</span><span class="p">,</span> <span class="n">Args</span><span class="p">);</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>This routine follows the same style as the other routines. (It expects
+to be called if the current token is a <tt class="docutils literal"><span class="pre">tok_identifier</span></tt> token). It
+also has recursion and error handling. One interesting aspect of this is
+that it uses <em>look-ahead</em> to determine if the current identifier is a
+stand alone variable reference or if it is a function call expression.
+It handles this by checking to see if the token after the identifier is
+a ‘(‘ token, constructing either a <tt class="docutils literal"><span class="pre">VariableExprAST</span></tt> or
+<tt class="docutils literal"><span class="pre">CallExprAST</span></tt> node as appropriate.</p>
+<p>Now that we have all of our simple expression-parsing logic in place, we
+can define a helper function to wrap it together into one entry point.
+We call this class of expressions “primary” expressions, for reasons
+that will become more clear <a class="reference external" href="LangImpl6.html#unary">later in the
+tutorial</a>. In order to parse an arbitrary
+primary expression, we need to determine what sort of expression it is:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">/// primary</span>
+<span class="c1">///   ::= identifierexpr</span>
+<span class="c1">///   ::= numberexpr</span>
+<span class="c1">///   ::= parenexpr</span>
+<span class="k">static</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="nf">ParsePrimary</span><span class="p">()</span> <span class="p">{</span>
+  <span class="k">switch</span> <span class="p">(</span><span class="n">CurTok</span><span class="p">)</span> <span class="p">{</span>
+  <span class="nl">default:</span> <span class="k">return</span> <span class="n">Error</span><span class="p">(</span><span class="s">"unknown token when expecting an expression"</span><span class="p">);</span>
+  <span class="k">case</span> <span class="n">tok_identifier</span>: <span class="k">return</span> <span class="n">ParseIdentifierExpr</span><span class="p">();</span>
+  <span class="k">case</span> <span class="n">tok_number</span>:     <span class="k">return</span> <span class="n">ParseNumberExpr</span><span class="p">();</span>
+  <span class="k">case</span> <span class="sc">'('</span>:            <span class="k">return</span> <span class="n">ParseParenExpr</span><span class="p">();</span>
+  <span class="p">}</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>Now that you see the definition of this function, it is more obvious why
+we can assume the state of CurTok in the various functions. This uses
+look-ahead to determine which sort of expression is being inspected, and
+then parses it with a function call.</p>
+<p>Now that basic expressions are handled, we need to handle binary
+expressions. They are a bit more complex.</p>
+</div>
+<div class="section" id="binary-expression-parsing">
+<h2><a class="toc-backref" href="#id6">2.5. Binary Expression Parsing</a><a class="headerlink" href="#binary-expression-parsing" title="Permalink to this headline">¶</a></h2>
+<p>Binary expressions are significantly harder to parse because they are
+often ambiguous. For example, when given the string “x+y*z”, the parser
+can choose to parse it as either “(x+y)*z” or “x+(y*z)”. With common
+definitions from mathematics, we expect the later parse, because “*”
+(multiplication) has higher <em>precedence</em> than “+” (addition).</p>
+<p>There are many ways to handle this, but an elegant and efficient way is
+to use <a class="reference external" href="http://en.wikipedia.org/wiki/Operator-precedence_parser">Operator-Precedence
+Parsing</a>.
+This parsing technique uses the precedence of binary operators to guide
+recursion. To start with, we need a table of precedences:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">/// BinopPrecedence - This holds the precedence for each binary operator that is</span>
+<span class="c1">/// defined.</span>
+<span class="k">static</span> <span class="n">std</span><span class="o">::</span><span class="n">map</span><span class="o"><</span><span class="kt">char</span><span class="p">,</span> <span class="kt">int</span><span class="o">></span> <span class="n">BinopPrecedence</span><span class="p">;</span>
+
+<span class="c1">/// GetTokPrecedence - Get the precedence of the pending binary operator token.</span>
+<span class="k">static</span> <span class="kt">int</span> <span class="nf">GetTokPrecedence</span><span class="p">()</span> <span class="p">{</span>
+  <span class="k">if</span> <span class="p">(</span><span class="o">!</span><span class="n">isascii</span><span class="p">(</span><span class="n">CurTok</span><span class="p">))</span>
+    <span class="k">return</span> <span class="o">-</span><span class="mi">1</span><span class="p">;</span>
+
+  <span class="c1">// Make sure it's a declared binop.</span>
+  <span class="kt">int</span> <span class="n">TokPrec</span> <span class="o">=</span> <span class="n">BinopPrecedence</span><span class="p">[</span><span class="n">CurTok</span><span class="p">];</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">TokPrec</span> <span class="o"><=</span> <span class="mi">0</span><span class="p">)</span> <span class="k">return</span> <span class="o">-</span><span class="mi">1</span><span class="p">;</span>
+  <span class="k">return</span> <span class="n">TokPrec</span><span class="p">;</span>
+<span class="p">}</span>
+
+<span class="kt">int</span> <span class="nf">main</span><span class="p">()</span> <span class="p">{</span>
+  <span class="c1">// Install standard binary operators.</span>
+  <span class="c1">// 1 is lowest precedence.</span>
+  <span class="n">BinopPrecedence</span><span class="p">[</span><span class="sc">'<'</span><span class="p">]</span> <span class="o">=</span> <span class="mi">10</span><span class="p">;</span>
+  <span class="n">BinopPrecedence</span><span class="p">[</span><span class="sc">'+'</span><span class="p">]</span> <span class="o">=</span> <span class="mi">20</span><span class="p">;</span>
+  <span class="n">BinopPrecedence</span><span class="p">[</span><span class="sc">'-'</span><span class="p">]</span> <span class="o">=</span> <span class="mi">20</span><span class="p">;</span>
+  <span class="n">BinopPrecedence</span><span class="p">[</span><span class="sc">'*'</span><span class="p">]</span> <span class="o">=</span> <span class="mi">40</span><span class="p">;</span>  <span class="c1">// highest.</span>
+  <span class="p">...</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>For the basic form of Kaleidoscope, we will only support 4 binary
+operators (this can obviously be extended by you, our brave and intrepid
+reader). The <tt class="docutils literal"><span class="pre">GetTokPrecedence</span></tt> function returns the precedence for
+the current token, or -1 if the token is not a binary operator. Having a
+map makes it easy to add new operators and makes it clear that the
+algorithm doesn’t depend on the specific operators involved, but it
+would be easy enough to eliminate the map and do the comparisons in the
+<tt class="docutils literal"><span class="pre">GetTokPrecedence</span></tt> function. (Or just use a fixed-size array).</p>
+<p>With the helper above defined, we can now start parsing binary
+expressions. The basic idea of operator precedence parsing is to break
+down an expression with potentially ambiguous binary operators into
+pieces. Consider ,for example, the expression “a+b+(c+d)*e*f+g”.
+Operator precedence parsing considers this as a stream of primary
+expressions separated by binary operators. As such, it will first parse
+the leading primary expression “a”, then it will see the pairs [+, b]
+[+, (c+d)] [*, e] [*, f] and [+, g]. Note that because parentheses are
+primary expressions, the binary expression parser doesn’t need to worry
+about nested subexpressions like (c+d) at all.</p>
+<p>To start, an expression is a primary expression potentially followed by
+a sequence of [binop,primaryexpr] pairs:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">/// expression</span>
+<span class="c1">///   ::= primary binoprhs</span>
+<span class="c1">///</span>
+<span class="k">static</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="nf">ParseExpression</span><span class="p">()</span> <span class="p">{</span>
+  <span class="n">ExprAST</span> <span class="o">*</span><span class="n">LHS</span> <span class="o">=</span> <span class="n">ParsePrimary</span><span class="p">();</span>
+  <span class="k">if</span> <span class="p">(</span><span class="o">!</span><span class="n">LHS</span><span class="p">)</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+
+  <span class="k">return</span> <span class="n">ParseBinOpRHS</span><span class="p">(</span><span class="mi">0</span><span class="p">,</span> <span class="n">LHS</span><span class="p">);</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p><tt class="docutils literal"><span class="pre">ParseBinOpRHS</span></tt> is the function that parses the sequence of pairs for
+us. It takes a precedence and a pointer to an expression for the part
+that has been parsed so far. Note that “x” is a perfectly valid
+expression: As such, “binoprhs” is allowed to be empty, in which case it
+returns the expression that is passed into it. In our example above, the
+code passes the expression for “a” into <tt class="docutils literal"><span class="pre">ParseBinOpRHS</span></tt> and the
+current token is “+”.</p>
+<p>The precedence value passed into <tt class="docutils literal"><span class="pre">ParseBinOpRHS</span></tt> indicates the
+<em>minimal operator precedence</em> that the function is allowed to eat. For
+example, if the current pair stream is [+, x] and <tt class="docutils literal"><span class="pre">ParseBinOpRHS</span></tt> is
+passed in a precedence of 40, it will not consume any tokens (because
+the precedence of ‘+’ is only 20). With this in mind, <tt class="docutils literal"><span class="pre">ParseBinOpRHS</span></tt>
+starts with:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">/// binoprhs</span>
+<span class="c1">///   ::= ('+' primary)*</span>
+<span class="k">static</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="nf">ParseBinOpRHS</span><span class="p">(</span><span class="kt">int</span> <span class="n">ExprPrec</span><span class="p">,</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="n">LHS</span><span class="p">)</span> <span class="p">{</span>
+  <span class="c1">// If this is a binop, find its precedence.</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="kt">int</span> <span class="n">TokPrec</span> <span class="o">=</span> <span class="n">GetTokPrecedence</span><span class="p">();</span>
+
+    <span class="c1">// If this is a binop that binds at least as tightly as the current binop,</span>
+    <span class="c1">// consume it, otherwise we are done.</span>
+    <span class="k">if</span> <span class="p">(</span><span class="n">TokPrec</span> <span class="o"><</span> <span class="n">ExprPrec</span><span class="p">)</span>
+      <span class="k">return</span> <span class="n">LHS</span><span class="p">;</span>
+</pre></div>
+</div>
+<p>This code gets the precedence of the current token and checks to see if
+if is too low. Because we defined invalid tokens to have a precedence of
+-1, this check implicitly knows that the pair-stream ends when the token
+stream runs out of binary operators. If this check succeeds, we know
+that the token is a binary operator and that it will be included in this
+expression:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">// Okay, we know this is a binop.</span>
+<span class="kt">int</span> <span class="n">BinOp</span> <span class="o">=</span> <span class="n">CurTok</span><span class="p">;</span>
+<span class="n">getNextToken</span><span class="p">();</span>  <span class="c1">// eat binop</span>
+
+<span class="c1">// Parse the primary expression after the binary operator.</span>
+<span class="n">ExprAST</span> <span class="o">*</span><span class="n">RHS</span> <span class="o">=</span> <span class="n">ParsePrimary</span><span class="p">();</span>
+<span class="k">if</span> <span class="p">(</span><span class="o">!</span><span class="n">RHS</span><span class="p">)</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+</pre></div>
+</div>
+<p>As such, this code eats (and remembers) the binary operator and then
+parses the primary expression that follows. This builds up the whole
+pair, the first of which is [+, b] for the running example.</p>
+<p>Now that we parsed the left-hand side of an expression and one pair of
+the RHS sequence, we have to decide which way the expression associates.
+In particular, we could have “(a+b) binop unparsed” or “a + (b binop
+unparsed)”. To determine this, we look ahead at “binop” to determine its
+precedence and compare it to BinOp’s precedence (which is ‘+’ in this
+case):</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">// If BinOp binds less tightly with RHS than the operator after RHS, let</span>
+<span class="c1">// the pending operator take RHS as its LHS.</span>
+<span class="kt">int</span> <span class="n">NextPrec</span> <span class="o">=</span> <span class="n">GetTokPrecedence</span><span class="p">();</span>
+<span class="k">if</span> <span class="p">(</span><span class="n">TokPrec</span> <span class="o"><</span> <span class="n">NextPrec</span><span class="p">)</span> <span class="p">{</span>
+</pre></div>
+</div>
+<p>If the precedence of the binop to the right of “RHS” is lower or equal
+to the precedence of our current operator, then we know that the
+parentheses associate as “(a+b) binop ...”. In our example, the current
+operator is “+” and the next operator is “+”, we know that they have the
+same precedence. In this case we’ll create the AST node for “a+b”, and
+then continue parsing:</p>
+<div class="highlight-c++"><div class="highlight"><pre>      <span class="p">...</span> <span class="k">if</span> <span class="n">body</span> <span class="n">omitted</span> <span class="p">...</span>
+    <span class="p">}</span>
+
+    <span class="c1">// Merge LHS/RHS.</span>
+    <span class="n">LHS</span> <span class="o">=</span> <span class="k">new</span> <span class="n">BinaryExprAST</span><span class="p">(</span><span class="n">BinOp</span><span class="p">,</span> <span class="n">LHS</span><span class="p">,</span> <span class="n">RHS</span><span class="p">);</span>
+  <span class="p">}</span>  <span class="c1">// loop around to the top of the while loop.</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>In our example above, this will turn “a+b+” into “(a+b)” and execute the
+next iteration of the loop, with “+” as the current token. The code
+above will eat, remember, and parse “(c+d)” as the primary expression,
+which makes the current pair equal to [+, (c+d)]. It will then evaluate
+the ‘if’ conditional above with “*” as the binop to the right of the
+primary. In this case, the precedence of “*” is higher than the
+precedence of “+” so the if condition will be entered.</p>
+<p>The critical question left here is “how can the if condition parse the
+right hand side in full”? In particular, to build the AST correctly for
+our example, it needs to get all of “(c+d)*e*f” as the RHS expression
+variable. The code to do this is surprisingly simple (code from the
+above two blocks duplicated for context):</p>
+<div class="highlight-c++"><div class="highlight"><pre>    <span class="c1">// If BinOp binds less tightly with RHS than the operator after RHS, let</span>
+    <span class="c1">// the pending operator take RHS as its LHS.</span>
+    <span class="kt">int</span> <span class="n">NextPrec</span> <span class="o">=</span> <span class="n">GetTokPrecedence</span><span class="p">();</span>
+    <span class="k">if</span> <span class="p">(</span><span class="n">TokPrec</span> <span class="o"><</span> <span class="n">NextPrec</span><span class="p">)</span> <span class="p">{</span>
+      <span class="n">RHS</span> <span class="o">=</span> <span class="n">ParseBinOpRHS</span><span class="p">(</span><span class="n">TokPrec</span><span class="o">+</span><span class="mi">1</span><span class="p">,</span> <span class="n">RHS</span><span class="p">);</span>
+      <span class="k">if</span> <span class="p">(</span><span class="n">RHS</span> <span class="o">==</span> <span class="mi">0</span><span class="p">)</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+    <span class="p">}</span>
+    <span class="c1">// Merge LHS/RHS.</span>
+    <span class="n">LHS</span> <span class="o">=</span> <span class="k">new</span> <span class="n">BinaryExprAST</span><span class="p">(</span><span class="n">BinOp</span><span class="p">,</span> <span class="n">LHS</span><span class="p">,</span> <span class="n">RHS</span><span class="p">);</span>
+  <span class="p">}</span>  <span class="c1">// loop around to the top of the while loop.</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>At this point, we know that the binary operator to the RHS of our
+primary has higher precedence than the binop we are currently parsing.
+As such, we know that any sequence of pairs whose operators are all
+higher precedence than “+” should be parsed together and returned as
+“RHS”. To do this, we recursively invoke the <tt class="docutils literal"><span class="pre">ParseBinOpRHS</span></tt> function
+specifying “TokPrec+1” as the minimum precedence required for it to
+continue. In our example above, this will cause it to return the AST
+node for “(c+d)*e*f” as RHS, which is then set as the RHS of the ‘+’
+expression.</p>
+<p>Finally, on the next iteration of the while loop, the “+g” piece is
+parsed and added to the AST. With this little bit of code (14
+non-trivial lines), we correctly handle fully general binary expression
+parsing in a very elegant way. This was a whirlwind tour of this code,
+and it is somewhat subtle. I recommend running through it with a few
+tough examples to see how it works.</p>
+<p>This wraps up handling of expressions. At this point, we can point the
+parser at an arbitrary token stream and build an expression from it,
+stopping at the first token that is not part of the expression. Next up
+we need to handle function definitions, etc.</p>
+</div>
+<div class="section" id="parsing-the-rest">
+<h2><a class="toc-backref" href="#id7">2.6. Parsing the Rest</a><a class="headerlink" href="#parsing-the-rest" title="Permalink to this headline">¶</a></h2>
+<p>The next thing missing is handling of function prototypes. In
+Kaleidoscope, these are used both for ‘extern’ function declarations as
+well as function body definitions. The code to do this is
+straight-forward and not very interesting (once you’ve survived
+expressions):</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">/// prototype</span>
+<span class="c1">///   ::= id '(' id* ')'</span>
+<span class="k">static</span> <span class="n">PrototypeAST</span> <span class="o">*</span><span class="nf">ParsePrototype</span><span class="p">()</span> <span class="p">{</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">CurTok</span> <span class="o">!=</span> <span class="n">tok_identifier</span><span class="p">)</span>
+    <span class="k">return</span> <span class="n">ErrorP</span><span class="p">(</span><span class="s">"Expected function name in prototype"</span><span class="p">);</span>
+
+  <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="n">FnName</span> <span class="o">=</span> <span class="n">IdentifierStr</span><span class="p">;</span>
+  <span class="n">getNextToken</span><span class="p">();</span>
+
+  <span class="k">if</span> <span class="p">(</span><span class="n">CurTok</span> <span class="o">!=</span> <span class="sc">'('</span><span class="p">)</span>
+    <span class="k">return</span> <span class="n">ErrorP</span><span class="p">(</span><span class="s">"Expected '(' in prototype"</span><span class="p">);</span>
+
+  <span class="c1">// Read the list of argument names.</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">string</span><span class="o">></span> <span class="n">ArgNames</span><span class="p">;</span>
+  <span class="k">while</span> <span class="p">(</span><span class="n">getNextToken</span><span class="p">()</span> <span class="o">==</span> <span class="n">tok_identifier</span><span class="p">)</span>
+    <span class="n">ArgNames</span><span class="p">.</span><span class="n">push_back</span><span class="p">(</span><span class="n">IdentifierStr</span><span class="p">);</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">CurTok</span> <span class="o">!=</span> <span class="sc">')'</span><span class="p">)</span>
+    <span class="k">return</span> <span class="n">ErrorP</span><span class="p">(</span><span class="s">"Expected ')' in prototype"</span><span class="p">);</span>
+
+  <span class="c1">// success.</span>
+  <span class="n">getNextToken</span><span class="p">();</span>  <span class="c1">// eat ')'.</span>
+
+  <span class="k">return</span> <span class="k">new</span> <span class="n">PrototypeAST</span><span class="p">(</span><span class="n">FnName</span><span class="p">,</span> <span class="n">ArgNames</span><span class="p">);</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>Given this, a function definition is very simple, just a prototype plus
+an expression to implement the body:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">/// definition ::= 'def' prototype expression</span>
+<span class="k">static</span> <span class="n">FunctionAST</span> <span class="o">*</span><span class="nf">ParseDefinition</span><span class="p">()</span> <span class="p">{</span>
+  <span class="n">getNextToken</span><span class="p">();</span>  <span class="c1">// eat def.</span>
+  <span class="n">PrototypeAST</span> <span class="o">*</span><span class="n">Proto</span> <span class="o">=</span> <span class="n">ParsePrototype</span><span class="p">();</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">Proto</span> <span class="o">==</span> <span class="mi">0</span><span class="p">)</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+
+  <span class="k">if</span> <span class="p">(</span><span class="n">ExprAST</span> <span class="o">*</span><span class="n">E</span> <span class="o">=</span> <span class="n">ParseExpression</span><span class="p">())</span>
+    <span class="k">return</span> <span class="k">new</span> <span class="n">FunctionAST</span><span class="p">(</span><span class="n">Proto</span><span class="p">,</span> <span class="n">E</span><span class="p">);</span>
+  <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>In addition, we support ‘extern’ to declare functions like ‘sin’ and
+‘cos’ as well as to support forward declaration of user functions. These
+‘extern’s are just prototypes with no body:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">/// external ::= 'extern' prototype</span>
+<span class="k">static</span> <span class="n">PrototypeAST</span> <span class="o">*</span><span class="nf">ParseExtern</span><span class="p">()</span> <span class="p">{</span>
+  <span class="n">getNextToken</span><span class="p">();</span>  <span class="c1">// eat extern.</span>
+  <span class="k">return</span> <span class="n">ParsePrototype</span><span class="p">();</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>Finally, we’ll also let the user type in arbitrary top-level expressions
+and evaluate them on the fly. We will handle this by defining anonymous
+nullary (zero argument) functions for them:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">/// toplevelexpr ::= expression</span>
+<span class="k">static</span> <span class="n">FunctionAST</span> <span class="o">*</span><span class="nf">ParseTopLevelExpr</span><span class="p">()</span> <span class="p">{</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">ExprAST</span> <span class="o">*</span><span class="n">E</span> <span class="o">=</span> <span class="n">ParseExpression</span><span class="p">())</span> <span class="p">{</span>
+    <span class="c1">// Make an anonymous proto.</span>
+    <span class="n">PrototypeAST</span> <span class="o">*</span><span class="n">Proto</span> <span class="o">=</span> <span class="k">new</span> <span class="n">PrototypeAST</span><span class="p">(</span><span class="s">""</span><span class="p">,</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">string</span><span class="o">></span><span class="p">());</span>
+    <span class="k">return</span> <span class="k">new</span> <span class="n">FunctionAST</span><span class="p">(</span><span class="n">Proto</span><span class="p">,</span> <span class="n">E</span><span class="p">);</span>
+  <span class="p">}</span>
+  <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>Now that we have all the pieces, let’s build a little driver that will
+let us actually <em>execute</em> this code we’ve built!</p>
+</div>
+<div class="section" id="the-driver">
+<h2><a class="toc-backref" href="#id8">2.7. The Driver</a><a class="headerlink" href="#the-driver" title="Permalink to this headline">¶</a></h2>
+<p>The driver for this simply invokes all of the parsing pieces with a
+top-level dispatch loop. There isn’t much interesting here, so I’ll just
+include the top-level loop. See <a class="reference external" href="#code">below</a> for full code in the
+“Top-Level Parsing” section.</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">/// top ::= definition | external | expression | ';'</span>
+<span class="k">static</span> <span class="kt">void</span> <span class="nf">MainLoop</span><span class="p">()</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">fprintf</span><span class="p">(</span><span class="n">stderr</span><span class="p">,</span> <span class="s">"ready> "</span><span class="p">);</span>
+    <span class="k">switch</span> <span class="p">(</span><span class="n">CurTok</span><span class="p">)</span> <span class="p">{</span>
+    <span class="k">case</span> <span class="n">tok_eof</span>:    <span class="k">return</span><span class="p">;</span>
+    <span class="k">case</span> <span class="sc">';'</span>:        <span class="n">getNextToken</span><span class="p">();</span> <span class="k">break</span><span class="p">;</span>  <span class="c1">// ignore top-level semicolons.</span>
+    <span class="k">case</span> <span class="n">tok_def</span>:    <span class="n">HandleDefinition</span><span class="p">();</span> <span class="k">break</span><span class="p">;</span>
+    <span class="k">case</span> <span class="n">tok_extern</span>: <span class="n">HandleExtern</span><span class="p">();</span> <span class="k">break</span><span class="p">;</span>
+    <span class="nl">default:</span>         <span class="n">HandleTopLevelExpression</span><span class="p">();</span> <span class="k">break</span><span class="p">;</span>
+    <span class="p">}</span>
+  <span class="p">}</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>The most interesting part of this is that we ignore top-level
+semicolons. Why is this, you ask? The basic reason is that if you type
+“4 + 5” at the command line, the parser doesn’t know whether that is the
+end of what you will type or not. For example, on the next line you
+could type “def foo...” in which case 4+5 is the end of a top-level
+expression. Alternatively you could type “* 6”, which would continue
+the expression. Having top-level semicolons allows you to type “4+5;”,
+and the parser will know you are done.</p>
+</div>
+<div class="section" id="conclusions">
+<h2><a class="toc-backref" href="#id9">2.8. Conclusions</a><a class="headerlink" href="#conclusions" title="Permalink to this headline">¶</a></h2>
+<p>With just under 400 lines of commented code (240 lines of non-comment,
+non-blank code), we fully defined our minimal language, including a
+lexer, parser, and AST builder. With this done, the executable will
+validate Kaleidoscope code and tell us if it is grammatically invalid.
+For example, here is a sample interaction:</p>
+<div class="highlight-bash"><pre>$ ./a.out
+ready> def foo(x y) x+foo(y, 4.0);
+Parsed a function definition.
+ready> def foo(x y) x+y y;
+Parsed a function definition.
+Parsed a top-level expr
+ready> def foo(x y) x+y );
+Parsed a function definition.
+Error: unknown token when expecting an expression
+ready> extern sin(a);
+ready> Parsed an extern
+ready> ^D
+$</pre>
+</div>
+<p>There is a lot of room for extension here. You can define new AST nodes,
+extend the language in many ways, etc. In the <a class="reference external" href="LangImpl3.html">next
+installment</a>, we will describe how to generate LLVM
+Intermediate Representation (IR) from the AST.</p>
+</div>
+<div class="section" id="full-code-listing">
+<h2><a class="toc-backref" href="#id10">2.9. 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 this and the previous chapter.
+Note that it is fully self-contained: you don’t need LLVM or any
+external libraries at all for this. (Besides the C and C++ standard
+libraries, of course.) To build this, just compile with:</p>
+<div class="highlight-bash"><div class="highlight"><pre><span class="c"># Compile</span>
+clang++ -g -O3 toy.cpp
+<span class="c"># Run</span>
+./a.out
+</pre></div>
+</div>
+<p>Here is the code:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="cp">#include <cctype></span>
+<span class="cp">#include <cstdio></span>
+<span class="cp">#include <cstdlib></span>
+<span class="cp">#include <map></span>
+<span class="cp">#include <string></span>
+<span class="cp">#include <vector></span>
+
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+<span class="c1">// Lexer</span>
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+
+<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="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>
+
+<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>
+
+  <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>
+
+  <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>
+
+  <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>
+  
+  <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>
+
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+<span class="c1">// Abstract Syntax Tree (aka Parse Tree)</span>
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+<span class="k">namespace</span> <span class="p">{</span>
+<span class="c1">/// ExprAST - Base class for all expression nodes.</span>
+<span class="k">class</span> <span class="nc">ExprAST</span> <span class="p">{</span>
+<span class="nl">public:</span>
+  <span class="k">virtual</span> <span class="o">~</span><span class="n">ExprAST</span><span class="p">()</span> <span class="p">{}</span>
+<span class="p">};</span>
+
+<span class="c1">/// NumberExprAST - Expression class for numeric literals like "1.0".</span>
+<span class="k">class</span> <span class="nc">NumberExprAST</span> <span class="o">:</span> <span class="k">public</span> <span class="n">ExprAST</span> <span class="p">{</span>
+<span class="nl">public:</span>
+  <span class="n">NumberExprAST</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="p">};</span>
+
+<span class="c1">/// VariableExprAST - Expression class for referencing a variable, like "a".</span>
+<span class="k">class</span> <span class="nc">VariableExprAST</span> <span class="o">:</span> <span class="k">public</span> <span class="n">ExprAST</span> <span class="p">{</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="nl">public:</span>
+  <span class="n">VariableExprAST</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="o">:</span> <span class="n">Name</span><span class="p">(</span><span class="n">name</span><span class="p">)</span> <span class="p">{}</span>
+<span class="p">};</span>
+
+<span class="c1">/// BinaryExprAST - Expression class for a binary operator.</span>
+<span class="k">class</span> <span class="nc">BinaryExprAST</span> <span class="o">:</span> <span class="k">public</span> <span class="n">ExprAST</span> <span class="p">{</span>
+<span class="nl">public:</span>
+  <span class="n">BinaryExprAST</span><span class="p">(</span><span class="kt">char</span> <span class="n">op</span><span class="p">,</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="n">lhs</span><span class="p">,</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="n">rhs</span><span class="p">)</span> <span class="p">{}</span>
+<span class="p">};</span>
+
+<span class="c1">/// CallExprAST - Expression class for function calls.</span>
+<span class="k">class</span> <span class="nc">CallExprAST</span> <span class="o">:</span> <span class="k">public</span> <span class="n">ExprAST</span> <span class="p">{</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="n">Callee</span><span class="p">;</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">vector</span><span class="o"><</span><span class="n">ExprAST</span><span class="o">*></span> <span class="n">Args</span><span class="p">;</span>
+<span class="nl">public:</span>
+  <span class="n">CallExprAST</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">callee</span><span class="p">,</span> <span class="n">std</span><span class="o">::</span><span class="n">vector</span><span class="o"><</span><span class="n">ExprAST</span><span class="o">*></span> <span class="o">&</span><span class="n">args</span><span class="p">)</span>
+    <span class="o">:</span> <span class="n">Callee</span><span class="p">(</span><span class="n">callee</span><span class="p">),</span> <span class="n">Args</span><span class="p">(</span><span class="n">args</span><span class="p">)</span> <span class="p">{}</span>
+<span class="p">};</span>
+
+<span class="c1">/// PrototypeAST - This class represents the "prototype" for a function,</span>
+<span class="c1">/// which captures its name, and its argument names (thus implicitly the number</span>
+<span class="c1">/// of arguments the function takes).</span>
+<span class="k">class</span> <span class="nc">PrototypeAST</span> <span class="p">{</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="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">string</span><span class="o">></span> <span class="n">Args</span><span class="p">;</span>
+<span class="nl">public:</span>
+  <span class="n">PrototypeAST</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="k">const</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">string</span><span class="o">></span> <span class="o">&</span><span class="n">args</span><span class="p">)</span>
+    <span class="o">:</span> <span class="n">Name</span><span class="p">(</span><span class="n">name</span><span class="p">),</span> <span class="n">Args</span><span class="p">(</span><span class="n">args</span><span class="p">)</span> <span class="p">{}</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="nl">public:</span>
+  <span class="n">FunctionAST</span><span class="p">(</span><span class="n">PrototypeAST</span> <span class="o">*</span><span class="n">proto</span><span class="p">,</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="n">body</span><span class="p">)</span> <span class="p">{}</span>
+<span class="p">};</span>
+<span class="p">}</span> <span class="c1">// end anonymous namespace</span>
+
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+<span class="c1">// Parser</span>
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+
+<span class="c1">/// CurTok/getNextToken - Provide a simple token buffer.  CurTok is the current</span>
+<span class="c1">/// token the parser is looking at.  getNextToken reads another token from the</span>
+<span class="c1">/// lexer and updates CurTok with its results.</span>
+<span class="k">static</span> <span class="kt">int</span> <span class="n">CurTok</span><span class="p">;</span>
+<span class="k">static</span> <span class="kt">int</span> <span class="nf">getNextToken</span><span class="p">()</span> <span class="p">{</span>
+  <span class="k">return</span> <span class="n">CurTok</span> <span class="o">=</span> <span class="n">gettok</span><span class="p">();</span>
+<span class="p">}</span>
+
+<span class="c1">/// BinopPrecedence - This holds the precedence for each binary operator that is</span>
+<span class="c1">/// defined.</span>
+<span class="k">static</span> <span class="n">std</span><span class="o">::</span><span class="n">map</span><span class="o"><</span><span class="kt">char</span><span class="p">,</span> <span class="kt">int</span><span class="o">></span> <span class="n">BinopPrecedence</span><span class="p">;</span>
+
+<span class="c1">/// GetTokPrecedence - Get the precedence of the pending binary operator token.</span>
+<span class="k">static</span> <span class="kt">int</span> <span class="nf">GetTokPrecedence</span><span class="p">()</span> <span class="p">{</span>
+  <span class="k">if</span> <span class="p">(</span><span class="o">!</span><span class="n">isascii</span><span class="p">(</span><span class="n">CurTok</span><span class="p">))</span>
+    <span class="k">return</span> <span class="o">-</span><span class="mi">1</span><span class="p">;</span>
+  
+  <span class="c1">// Make sure it's a declared binop.</span>
+  <span class="kt">int</span> <span class="n">TokPrec</span> <span class="o">=</span> <span class="n">BinopPrecedence</span><span class="p">[</span><span class="n">CurTok</span><span class="p">];</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">TokPrec</span> <span class="o"><=</span> <span class="mi">0</span><span class="p">)</span> <span class="k">return</span> <span class="o">-</span><span class="mi">1</span><span class="p">;</span>
+  <span class="k">return</span> <span class="n">TokPrec</span><span class="p">;</span>
+<span class="p">}</span>
+
+<span class="c1">/// Error* - These are little helper functions for error handling.</span>
+<span class="n">ExprAST</span> <span class="o">*</span><span class="nf">Error</span><span class="p">(</span><span class="k">const</span> <span class="kt">char</span> <span class="o">*</span><span class="n">Str</span><span class="p">)</span> <span class="p">{</span> <span class="n">fprintf</span><span class="p">(</span><span class="n">stderr</span><span class="p">,</span> <span class="s">"Error: %s</span><span class="se">\n</span><span class="s">"</span><span class="p">,</span> <span class="n">Str</span><span class="p">);</span><span class="k">return</span> <span class="mi">0</span><span class="p">;}</span>
+<span class="n">PrototypeAST</span> <span class="o">*</span><span class="nf">ErrorP</span><span class="p">(</span><span class="k">const</span> <span class="kt">char</span> <span class="o">*</span><span class="n">Str</span><span class="p">)</span> <span class="p">{</span> <span class="n">Error</span><span class="p">(</span><span class="n">Str</span><span class="p">);</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span> <span class="p">}</span>
+
+<span class="k">static</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="nf">ParseExpression</span><span class="p">();</span>
+
+<span class="c1">/// identifierexpr</span>
+<span class="c1">///   ::= identifier</span>
+<span class="c1">///   ::= identifier '(' expression* ')'</span>
+<span class="k">static</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="nf">ParseIdentifierExpr</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">IdName</span> <span class="o">=</span> <span class="n">IdentifierStr</span><span class="p">;</span>
+  
+  <span class="n">getNextToken</span><span class="p">();</span>  <span class="c1">// eat identifier.</span>
+  
+  <span class="k">if</span> <span class="p">(</span><span class="n">CurTok</span> <span class="o">!=</span> <span class="sc">'('</span><span class="p">)</span> <span class="c1">// Simple variable ref.</span>
+    <span class="k">return</span> <span class="k">new</span> <span class="n">VariableExprAST</span><span class="p">(</span><span class="n">IdName</span><span class="p">);</span>
+  
+  <span class="c1">// Call.</span>
+  <span class="n">getNextToken</span><span class="p">();</span>  <span class="c1">// eat (</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">vector</span><span class="o"><</span><span class="n">ExprAST</span><span class="o">*></span> <span class="n">Args</span><span class="p">;</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">CurTok</span> <span class="o">!=</span> <span class="sc">')'</span><span class="p">)</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">ExprAST</span> <span class="o">*</span><span class="n">Arg</span> <span class="o">=</span> <span class="n">ParseExpression</span><span class="p">();</span>
+      <span class="k">if</span> <span class="p">(</span><span class="o">!</span><span class="n">Arg</span><span class="p">)</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+      <span class="n">Args</span><span class="p">.</span><span class="n">push_back</span><span class="p">(</span><span class="n">Arg</span><span class="p">);</span>
+
+      <span class="k">if</span> <span class="p">(</span><span class="n">CurTok</span> <span class="o">==</span> <span class="sc">')'</span><span class="p">)</span> <span class="k">break</span><span class="p">;</span>
+
+      <span class="k">if</span> <span class="p">(</span><span class="n">CurTok</span> <span class="o">!=</span> <span class="sc">','</span><span class="p">)</span>
+        <span class="k">return</span> <span class="n">Error</span><span class="p">(</span><span class="s">"Expected ')' or ',' in argument list"</span><span class="p">);</span>
+      <span class="n">getNextToken</span><span class="p">();</span>
+    <span class="p">}</span>
+  <span class="p">}</span>
+
+  <span class="c1">// Eat the ')'.</span>
+  <span class="n">getNextToken</span><span class="p">();</span>
+  
+  <span class="k">return</span> <span class="k">new</span> <span class="n">CallExprAST</span><span class="p">(</span><span class="n">IdName</span><span class="p">,</span> <span class="n">Args</span><span class="p">);</span>
+<span class="p">}</span>
+
+<span class="c1">/// numberexpr ::= number</span>
+<span class="k">static</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="nf">ParseNumberExpr</span><span class="p">()</span> <span class="p">{</span>
+  <span class="n">ExprAST</span> <span class="o">*</span><span class="n">Result</span> <span class="o">=</span> <span class="k">new</span> <span class="n">NumberExprAST</span><span class="p">(</span><span class="n">NumVal</span><span class="p">);</span>
+  <span class="n">getNextToken</span><span class="p">();</span> <span class="c1">// consume the number</span>
+  <span class="k">return</span> <span class="n">Result</span><span class="p">;</span>
+<span class="p">}</span>
+
+<span class="c1">/// parenexpr ::= '(' expression ')'</span>
+<span class="k">static</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="nf">ParseParenExpr</span><span class="p">()</span> <span class="p">{</span>
+  <span class="n">getNextToken</span><span class="p">();</span>  <span class="c1">// eat (.</span>
+  <span class="n">ExprAST</span> <span class="o">*</span><span class="n">V</span> <span class="o">=</span> <span class="n">ParseExpression</span><span class="p">();</span>
+  <span class="k">if</span> <span class="p">(</span><span class="o">!</span><span class="n">V</span><span class="p">)</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+  
+  <span class="k">if</span> <span class="p">(</span><span class="n">CurTok</span> <span class="o">!=</span> <span class="sc">')'</span><span class="p">)</span>
+    <span class="k">return</span> <span class="n">Error</span><span class="p">(</span><span class="s">"expected ')'"</span><span class="p">);</span>
+  <span class="n">getNextToken</span><span class="p">();</span>  <span class="c1">// eat ).</span>
+  <span class="k">return</span> <span class="n">V</span><span class="p">;</span>
+<span class="p">}</span>
+
+<span class="c1">/// primary</span>
+<span class="c1">///   ::= identifierexpr</span>
+<span class="c1">///   ::= numberexpr</span>
+<span class="c1">///   ::= parenexpr</span>
+<span class="k">static</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="nf">ParsePrimary</span><span class="p">()</span> <span class="p">{</span>
+  <span class="k">switch</span> <span class="p">(</span><span class="n">CurTok</span><span class="p">)</span> <span class="p">{</span>
+  <span class="nl">default:</span> <span class="k">return</span> <span class="n">Error</span><span class="p">(</span><span class="s">"unknown token when expecting an expression"</span><span class="p">);</span>
+  <span class="k">case</span> <span class="n">tok_identifier</span>: <span class="k">return</span> <span class="n">ParseIdentifierExpr</span><span class="p">();</span>
+  <span class="k">case</span> <span class="n">tok_number</span>:     <span class="k">return</span> <span class="n">ParseNumberExpr</span><span class="p">();</span>
+  <span class="k">case</span> <span class="sc">'('</span>:            <span class="k">return</span> <span class="n">ParseParenExpr</span><span class="p">();</span>
+  <span class="p">}</span>
+<span class="p">}</span>
+
+<span class="c1">/// binoprhs</span>
+<span class="c1">///   ::= ('+' primary)*</span>
+<span class="k">static</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="nf">ParseBinOpRHS</span><span class="p">(</span><span class="kt">int</span> <span class="n">ExprPrec</span><span class="p">,</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="n">LHS</span><span class="p">)</span> <span class="p">{</span>
+  <span class="c1">// If this is a binop, find its precedence.</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="kt">int</span> <span class="n">TokPrec</span> <span class="o">=</span> <span class="n">GetTokPrecedence</span><span class="p">();</span>
+    
+    <span class="c1">// If this is a binop that binds at least as tightly as the current binop,</span>
+    <span class="c1">// consume it, otherwise we are done.</span>
+    <span class="k">if</span> <span class="p">(</span><span class="n">TokPrec</span> <span class="o"><</span> <span class="n">ExprPrec</span><span class="p">)</span>
+      <span class="k">return</span> <span class="n">LHS</span><span class="p">;</span>
+    
+    <span class="c1">// Okay, we know this is a binop.</span>
+    <span class="kt">int</span> <span class="n">BinOp</span> <span class="o">=</span> <span class="n">CurTok</span><span class="p">;</span>
+    <span class="n">getNextToken</span><span class="p">();</span>  <span class="c1">// eat binop</span>
+    
+    <span class="c1">// Parse the primary expression after the binary operator.</span>
+    <span class="n">ExprAST</span> <span class="o">*</span><span class="n">RHS</span> <span class="o">=</span> <span class="n">ParsePrimary</span><span class="p">();</span>
+    <span class="k">if</span> <span class="p">(</span><span class="o">!</span><span class="n">RHS</span><span class="p">)</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+    
+    <span class="c1">// If BinOp binds less tightly with RHS than the operator after RHS, let</span>
+    <span class="c1">// the pending operator take RHS as its LHS.</span>
+    <span class="kt">int</span> <span class="n">NextPrec</span> <span class="o">=</span> <span class="n">GetTokPrecedence</span><span class="p">();</span>
+    <span class="k">if</span> <span class="p">(</span><span class="n">TokPrec</span> <span class="o"><</span> <span class="n">NextPrec</span><span class="p">)</span> <span class="p">{</span>
+      <span class="n">RHS</span> <span class="o">=</span> <span class="n">ParseBinOpRHS</span><span class="p">(</span><span class="n">TokPrec</span><span class="o">+</span><span class="mi">1</span><span class="p">,</span> <span class="n">RHS</span><span class="p">);</span>
+      <span class="k">if</span> <span class="p">(</span><span class="n">RHS</span> <span class="o">==</span> <span class="mi">0</span><span class="p">)</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+    <span class="p">}</span>
+    
+    <span class="c1">// Merge LHS/RHS.</span>
+    <span class="n">LHS</span> <span class="o">=</span> <span class="k">new</span> <span class="n">BinaryExprAST</span><span class="p">(</span><span class="n">BinOp</span><span class="p">,</span> <span class="n">LHS</span><span class="p">,</span> <span class="n">RHS</span><span class="p">);</span>
+  <span class="p">}</span>
+<span class="p">}</span>
+
+<span class="c1">/// expression</span>
+<span class="c1">///   ::= primary binoprhs</span>
+<span class="c1">///</span>
+<span class="k">static</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="nf">ParseExpression</span><span class="p">()</span> <span class="p">{</span>
+  <span class="n">ExprAST</span> <span class="o">*</span><span class="n">LHS</span> <span class="o">=</span> <span class="n">ParsePrimary</span><span class="p">();</span>
+  <span class="k">if</span> <span class="p">(</span><span class="o">!</span><span class="n">LHS</span><span class="p">)</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+  
+  <span class="k">return</span> <span class="n">ParseBinOpRHS</span><span class="p">(</span><span class="mi">0</span><span class="p">,</span> <span class="n">LHS</span><span class="p">);</span>
+<span class="p">}</span>
+
+<span class="c1">/// prototype</span>
+<span class="c1">///   ::= id '(' id* ')'</span>
+<span class="k">static</span> <span class="n">PrototypeAST</span> <span class="o">*</span><span class="nf">ParsePrototype</span><span class="p">()</span> <span class="p">{</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">CurTok</span> <span class="o">!=</span> <span class="n">tok_identifier</span><span class="p">)</span>
+    <span class="k">return</span> <span class="n">ErrorP</span><span class="p">(</span><span class="s">"Expected function name in prototype"</span><span class="p">);</span>
+
+  <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="n">FnName</span> <span class="o">=</span> <span class="n">IdentifierStr</span><span class="p">;</span>
+  <span class="n">getNextToken</span><span class="p">();</span>
+  
+  <span class="k">if</span> <span class="p">(</span><span class="n">CurTok</span> <span class="o">!=</span> <span class="sc">'('</span><span class="p">)</span>
+    <span class="k">return</span> <span class="n">ErrorP</span><span class="p">(</span><span class="s">"Expected '(' in prototype"</span><span class="p">);</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">string</span><span class="o">></span> <span class="n">ArgNames</span><span class="p">;</span>
+  <span class="k">while</span> <span class="p">(</span><span class="n">getNextToken</span><span class="p">()</span> <span class="o">==</span> <span class="n">tok_identifier</span><span class="p">)</span>
+    <span class="n">ArgNames</span><span class="p">.</span><span class="n">push_back</span><span class="p">(</span><span class="n">IdentifierStr</span><span class="p">);</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">CurTok</span> <span class="o">!=</span> <span class="sc">')'</span><span class="p">)</span>
+    <span class="k">return</span> <span class="n">ErrorP</span><span class="p">(</span><span class="s">"Expected ')' in prototype"</span><span class="p">);</span>
+  
+  <span class="c1">// success.</span>
+  <span class="n">getNextToken</span><span class="p">();</span>  <span class="c1">// eat ')'.</span>
+  
+  <span class="k">return</span> <span class="k">new</span> <span class="n">PrototypeAST</span><span class="p">(</span><span class="n">FnName</span><span class="p">,</span> <span class="n">ArgNames</span><span class="p">);</span>
+<span class="p">}</span>
+
+<span class="c1">/// definition ::= 'def' prototype expression</span>
+<span class="k">static</span> <span class="n">FunctionAST</span> <span class="o">*</span><span class="nf">ParseDefinition</span><span class="p">()</span> <span class="p">{</span>
+  <span class="n">getNextToken</span><span class="p">();</span>  <span class="c1">// eat def.</span>
+  <span class="n">PrototypeAST</span> <span class="o">*</span><span class="n">Proto</span> <span class="o">=</span> <span class="n">ParsePrototype</span><span class="p">();</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">Proto</span> <span class="o">==</span> <span class="mi">0</span><span class="p">)</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+
+  <span class="k">if</span> <span class="p">(</span><span class="n">ExprAST</span> <span class="o">*</span><span class="n">E</span> <span class="o">=</span> <span class="n">ParseExpression</span><span class="p">())</span>
+    <span class="k">return</span> <span class="k">new</span> <span class="n">FunctionAST</span><span class="p">(</span><span class="n">Proto</span><span class="p">,</span> <span class="n">E</span><span class="p">);</span>
+  <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+<span class="p">}</span>
+
+<span class="c1">/// toplevelexpr ::= expression</span>
+<span class="k">static</span> <span class="n">FunctionAST</span> <span class="o">*</span><span class="nf">ParseTopLevelExpr</span><span class="p">()</span> <span class="p">{</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">ExprAST</span> <span class="o">*</span><span class="n">E</span> <span class="o">=</span> <span class="n">ParseExpression</span><span class="p">())</span> <span class="p">{</span>
+    <span class="c1">// Make an anonymous proto.</span>
+    <span class="n">PrototypeAST</span> <span class="o">*</span><span class="n">Proto</span> <span class="o">=</span> <span class="k">new</span> <span class="n">PrototypeAST</span><span class="p">(</span><span class="s">""</span><span class="p">,</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">string</span><span class="o">></span><span class="p">());</span>
+    <span class="k">return</span> <span class="k">new</span> <span class="n">FunctionAST</span><span class="p">(</span><span class="n">Proto</span><span class="p">,</span> <span class="n">E</span><span class="p">);</span>
+  <span class="p">}</span>
+  <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+<span class="p">}</span>
+
+<span class="c1">/// external ::= 'extern' prototype</span>
+<span class="k">static</span> <span class="n">PrototypeAST</span> <span class="o">*</span><span class="nf">ParseExtern</span><span class="p">()</span> <span class="p">{</span>
+  <span class="n">getNextToken</span><span class="p">();</span>  <span class="c1">// eat extern.</span>
+  <span class="k">return</span> <span class="n">ParsePrototype</span><span class="p">();</span>
+<span class="p">}</span>
+
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+<span class="c1">// Top-Level parsing</span>
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+
+<span class="k">static</span> <span class="kt">void</span> <span class="nf">HandleDefinition</span><span class="p">()</span> <span class="p">{</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">ParseDefinition</span><span class="p">())</span> <span class="p">{</span>
+    <span class="n">fprintf</span><span class="p">(</span><span class="n">stderr</span><span class="p">,</span> <span class="s">"Parsed a function definition.</span><span class="se">\n</span><span class="s">"</span><span class="p">);</span>
+  <span class="p">}</span> <span class="k">else</span> <span class="p">{</span>
+    <span class="c1">// Skip token for error recovery.</span>
+    <span class="n">getNextToken</span><span class="p">();</span>
+  <span class="p">}</span>
+<span class="p">}</span>
+
+<span class="k">static</span> <span class="kt">void</span> <span class="nf">HandleExtern</span><span class="p">()</span> <span class="p">{</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">ParseExtern</span><span class="p">())</span> <span class="p">{</span>
+    <span class="n">fprintf</span><span class="p">(</span><span class="n">stderr</span><span class="p">,</span> <span class="s">"Parsed an extern</span><span class="se">\n</span><span class="s">"</span><span class="p">);</span>
+  <span class="p">}</span> <span class="k">else</span> <span class="p">{</span>
+    <span class="c1">// Skip token for error recovery.</span>
+    <span class="n">getNextToken</span><span class="p">();</span>
+  <span class="p">}</span>
+<span class="p">}</span>
+
+<span class="k">static</span> <span class="kt">void</span> <span class="nf">HandleTopLevelExpression</span><span class="p">()</span> <span class="p">{</span>
+  <span class="c1">// Evaluate a top-level expression into an anonymous function.</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">ParseTopLevelExpr</span><span class="p">())</span> <span class="p">{</span>
+    <span class="n">fprintf</span><span class="p">(</span><span class="n">stderr</span><span class="p">,</span> <span class="s">"Parsed a top-level expr</span><span class="se">\n</span><span class="s">"</span><span class="p">);</span>
+  <span class="p">}</span> <span class="k">else</span> <span class="p">{</span>
+    <span class="c1">// Skip token for error recovery.</span>
+    <span class="n">getNextToken</span><span class="p">();</span>
+  <span class="p">}</span>
+<span class="p">}</span>
+
+<span class="c1">/// top ::= definition | external | expression | ';'</span>
+<span class="k">static</span> <span class="kt">void</span> <span class="nf">MainLoop</span><span class="p">()</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">fprintf</span><span class="p">(</span><span class="n">stderr</span><span class="p">,</span> <span class="s">"ready> "</span><span class="p">);</span>
+    <span class="k">switch</span> <span class="p">(</span><span class="n">CurTok</span><span class="p">)</span> <span class="p">{</span>
+    <span class="k">case</span> <span class="n">tok_eof</span>:    <span class="k">return</span><span class="p">;</span>
+    <span class="k">case</span> <span class="sc">';'</span>:        <span class="n">getNextToken</span><span class="p">();</span> <span class="k">break</span><span class="p">;</span>  <span class="c1">// ignore top-level semicolons.</span>
+    <span class="k">case</span> <span class="n">tok_def</span>:    <span class="n">HandleDefinition</span><span class="p">();</span> <span class="k">break</span><span class="p">;</span>
+    <span class="k">case</span> <span class="n">tok_extern</span>: <span class="n">HandleExtern</span><span class="p">();</span> <span class="k">break</span><span class="p">;</span>
+    <span class="nl">default:</span>         <span class="n">HandleTopLevelExpression</span><span class="p">();</span> <span class="k">break</span><span class="p">;</span>
+    <span class="p">}</span>
+  <span class="p">}</span>
+<span class="p">}</span>
+
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+<span class="c1">// Main driver code.</span>
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+
+<span class="kt">int</span> <span class="nf">main</span><span class="p">()</span> <span class="p">{</span>
+  <span class="c1">// Install standard binary operators.</span>
+  <span class="c1">// 1 is lowest precedence.</span>
+  <span class="n">BinopPrecedence</span><span class="p">[</span><span class="sc">'<'</span><span class="p">]</span> <span class="o">=</span> <span class="mi">10</span><span class="p">;</span>
+  <span class="n">BinopPrecedence</span><span class="p">[</span><span class="sc">'+'</span><span class="p">]</span> <span class="o">=</span> <span class="mi">20</span><span class="p">;</span>
+  <span class="n">BinopPrecedence</span><span class="p">[</span><span class="sc">'-'</span><span class="p">]</span> <span class="o">=</span> <span class="mi">20</span><span class="p">;</span>
+  <span class="n">BinopPrecedence</span><span class="p">[</span><span class="sc">'*'</span><span class="p">]</span> <span class="o">=</span> <span class="mi">40</span><span class="p">;</span>  <span class="c1">// highest.</span>
+
+  <span class="c1">// Prime the first token.</span>
+  <span class="n">fprintf</span><span class="p">(</span><span class="n">stderr</span><span class="p">,</span> <span class="s">"ready> "</span><span class="p">);</span>
+  <span class="n">getNextToken</span><span class="p">();</span>
+
+  <span class="c1">// Run the main "interpreter loop" now.</span>
+  <span class="n">MainLoop</span><span class="p">();</span>
+
+  <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p><a class="reference external" href="LangImpl3.html">Next: Implementing Code Generation to LLVM IR</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="LangImpl3.html" title="3. Kaleidoscope: Code generation to LLVM IR"
+             >next</a> |</li>
+        <li class="right" >
+          <a href="LangImpl1.html" title="1. Kaleidoscope: Tutorial Introduction and the Lexer"
+             >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-2014, LLVM Project.
+      Last updated on 2015-05-25.
+      Created using <a href="http://sphinx.pocoo.org/">Sphinx</a> 1.1.3.
+    </div>
+  </body>
+</html>
\ No newline at end of file

Added: www-releases/trunk/3.6.1/docs/tutorial/LangImpl3.html
URL: http://llvm.org/viewvc/llvm-project/www-releases/trunk/3.6.1/docs/tutorial/LangImpl3.html?rev=238135&view=auto
==============================================================================
--- www-releases/trunk/3.6.1/docs/tutorial/LangImpl3.html (added)
+++ www-releases/trunk/3.6.1/docs/tutorial/LangImpl3.html Mon May 25 08:53:02 2015
@@ -0,0 +1,1188 @@
+
+
+<!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. Kaleidoscope: Code generation to LLVM IR — LLVM 3.6 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.6',
+        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.6 documentation" href="../index.html" />
+    <link rel="up" title="LLVM Tutorial: Table of Contents" href="index.html" />
+    <link rel="next" title="4. Kaleidoscope: Adding JIT and Optimizer Support" href="LangImpl4.html" />
+    <link rel="prev" title="2. Kaleidoscope: Implementing a Parser and AST" href="LangImpl2.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="LangImpl4.html" title="4. Kaleidoscope: Adding JIT and Optimizer Support"
+             accesskey="N">next</a> |</li>
+        <li class="right" >
+          <a href="LangImpl2.html" title="2. Kaleidoscope: Implementing a Parser and AST"
+             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-code-generation-to-llvm-ir">
+<h1>3. Kaleidoscope: Code generation to LLVM IR<a class="headerlink" href="#kaleidoscope-code-generation-to-llvm-ir" 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="#code-generation-setup" id="id2">Code Generation Setup</a></li>
+<li><a class="reference internal" href="#expression-code-generation" id="id3">Expression Code Generation</a></li>
+<li><a class="reference internal" href="#function-code-generation" id="id4">Function Code Generation</a></li>
+<li><a class="reference internal" href="#driver-changes-and-closing-thoughts" id="id5">Driver Changes and Closing Thoughts</a></li>
+<li><a class="reference internal" href="#full-code-listing" id="id6">Full Code Listing</a></li>
+</ul>
+</div>
+<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 “<a class="reference external" href="index.html">Implementing a language with
+LLVM</a>” tutorial. This chapter shows you how to transform
+the <a class="reference external" href="LangImpl2.html">Abstract Syntax Tree</a>, built in Chapter 2, into
+LLVM IR. This will teach you a little bit about how LLVM does things, as
+well as demonstrate how easy it is to use. It’s much more work to build
+a lexer and parser than it is to generate LLVM IR code. :)</p>
+<p><strong>Please note</strong>: the code in this chapter and later require LLVM 2.2 or
+later. LLVM 2.1 and before will not work with it. Also note that you
+need to use a version of this tutorial that matches your LLVM release:
+If you are using an official LLVM release, use the version of the
+documentation included with your release or on the <a class="reference external" href="http://llvm.org/releases/">llvm.org releases
+page</a>.</p>
+</div>
+<div class="section" id="code-generation-setup">
+<h2><a class="toc-backref" href="#id2">3.2. Code Generation Setup</a><a class="headerlink" href="#code-generation-setup" title="Permalink to this headline">¶</a></h2>
+<p>In order to generate LLVM IR, we want some simple setup to get started.
+First we define virtual code generation (codegen) methods in each AST
+class:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">/// ExprAST - Base class for all expression nodes.</span>
+<span class="k">class</span> <span class="nc">ExprAST</span> <span class="p">{</span>
+<span class="nl">public:</span>
+  <span class="k">virtual</span> <span class="o">~</span><span class="n">ExprAST</span><span class="p">()</span> <span class="p">{}</span>
+  <span class="k">virtual</span> <span class="n">Value</span> <span class="o">*</span><span class="n">Codegen</span><span class="p">()</span> <span class="o">=</span> <span class="mi">0</span><span class="p">;</span>
+<span class="p">};</span>
+
+<span class="c1">/// NumberExprAST - Expression class for numeric literals like "1.0".</span>
+<span class="k">class</span> <span class="nc">NumberExprAST</span> <span class="o">:</span> <span class="k">public</span> <span class="n">ExprAST</span> <span class="p">{</span>
+  <span class="kt">double</span> <span class="n">Val</span><span class="p">;</span>
+<span class="nl">public:</span>
+  <span class="n">NumberExprAST</span><span class="p">(</span><span class="kt">double</span> <span class="n">val</span><span class="p">)</span> <span class="o">:</span> <span class="n">Val</span><span class="p">(</span><span class="n">val</span><span class="p">)</span> <span class="p">{}</span>
+  <span class="k">virtual</span> <span class="n">Value</span> <span class="o">*</span><span class="n">Codegen</span><span class="p">();</span>
+<span class="p">};</span>
+<span class="p">...</span>
+</pre></div>
+</div>
+<p>The Codegen() method says to emit IR for that AST node along with all
+the things it depends on, and they all return an LLVM Value object.
+“Value” is the class used to represent a “<a class="reference external" href="http://en.wikipedia.org/wiki/Static_single_assignment_form">Static Single Assignment
+(SSA)</a>
+register” or “SSA value” in LLVM. The most distinct aspect of SSA values
+is that their value is computed as the related instruction executes, and
+it does not get a new value until (and if) the instruction re-executes.
+In other words, there is no way to “change” an SSA value. For more
+information, please read up on <a class="reference external" href="http://en.wikipedia.org/wiki/Static_single_assignment_form">Static Single
+Assignment</a>
+- the concepts are really quite natural once you grok them.</p>
+<p>Note that instead of adding virtual methods to the ExprAST class
+hierarchy, it could also make sense to use a <a class="reference external" href="http://en.wikipedia.org/wiki/Visitor_pattern">visitor
+pattern</a> or some other
+way to model this. Again, this tutorial won’t dwell on good software
+engineering practices: for our purposes, adding a virtual method is
+simplest.</p>
+<p>The second thing we want is an “Error” method like we used for the
+parser, which will be used to report errors found during code generation
+(for example, use of an undeclared parameter):</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="n">Value</span> <span class="o">*</span><span class="nf">ErrorV</span><span class="p">(</span><span class="k">const</span> <span class="kt">char</span> <span class="o">*</span><span class="n">Str</span><span class="p">)</span> <span class="p">{</span> <span class="n">Error</span><span class="p">(</span><span class="n">Str</span><span class="p">);</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span> <span class="p">}</span>
+
+<span class="k">static</span> <span class="n">Module</span> <span class="o">*</span><span class="n">TheModule</span><span class="p">;</span>
+<span class="k">static</span> <span class="n">IRBuilder</span><span class="o"><></span> <span class="n">Builder</span><span class="p">(</span><span class="n">getGlobalContext</span><span class="p">());</span>
+<span class="k">static</span> <span class="n">std</span><span class="o">::</span><span class="n">map</span><span class="o"><</span><span class="n">std</span><span class="o">::</span><span class="n">string</span><span class="p">,</span> <span class="n">Value</span><span class="o">*></span> <span class="n">NamedValues</span><span class="p">;</span>
+</pre></div>
+</div>
+<p>The static variables will be used during code generation. <tt class="docutils literal"><span class="pre">TheModule</span></tt>
+is the LLVM construct that contains all of the functions and global
+variables in a chunk of code. In many ways, it is the top-level
+structure that the LLVM IR uses to contain code.</p>
+<p>The <tt class="docutils literal"><span class="pre">Builder</span></tt> object is a helper object that makes it easy to generate
+LLVM instructions. Instances of the
+<tt class="docutils literal"><span class="pre">`IRBuilder</span></tt> <<a class="reference external" href="http://llvm.org/doxygen/IRBuilder_8h-source.html">http://llvm.org/doxygen/IRBuilder_8h-source.html</a>>`_
+class template keep track of the current place to insert instructions
+and has methods to create new instructions.</p>
+<p>The <tt class="docutils literal"><span class="pre">NamedValues</span></tt> map keeps track of which values are defined in the
+current scope and what their LLVM representation is. (In other words, it
+is a symbol table for the code). In this form of Kaleidoscope, the only
+things that can be referenced are function parameters. As such, function
+parameters will be in this map when generating code for their function
+body.</p>
+<p>With these basics in place, we can start talking about how to generate
+code for each expression. Note that this assumes that the <tt class="docutils literal"><span class="pre">Builder</span></tt>
+has been set up to generate code <em>into</em> something. For now, we’ll assume
+that this has already been done, and we’ll just use it to emit code.</p>
+</div>
+<div class="section" id="expression-code-generation">
+<h2><a class="toc-backref" href="#id3">3.3. Expression Code Generation</a><a class="headerlink" href="#expression-code-generation" title="Permalink to this headline">¶</a></h2>
+<p>Generating LLVM code for expression nodes is very straightforward: less
+than 45 lines of commented code for all four of our expression nodes.
+First we’ll do numeric literals:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="n">Value</span> <span class="o">*</span><span class="n">NumberExprAST</span><span class="o">::</span><span class="n">Codegen</span><span class="p">()</span> <span class="p">{</span>
+  <span class="k">return</span> <span class="n">ConstantFP</span><span class="o">::</span><span class="n">get</span><span class="p">(</span><span class="n">getGlobalContext</span><span class="p">(),</span> <span class="n">APFloat</span><span class="p">(</span><span class="n">Val</span><span class="p">));</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>In the LLVM IR, numeric constants are represented with the
+<tt class="docutils literal"><span class="pre">ConstantFP</span></tt> class, which holds the numeric value in an <tt class="docutils literal"><span class="pre">APFloat</span></tt>
+internally (<tt class="docutils literal"><span class="pre">APFloat</span></tt> has the capability of holding floating point
+constants of Arbitrary Precision). This code basically just creates
+and returns a <tt class="docutils literal"><span class="pre">ConstantFP</span></tt>. Note that in the LLVM IR that constants
+are all uniqued together and shared. For this reason, the API uses the
+“foo::get(...)” idiom instead of “new foo(..)” or “foo::Create(..)”.</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="n">Value</span> <span class="o">*</span><span class="n">VariableExprAST</span><span class="o">::</span><span class="n">Codegen</span><span class="p">()</span> <span class="p">{</span>
+  <span class="c1">// Look this variable up in the function.</span>
+  <span class="n">Value</span> <span class="o">*</span><span class="n">V</span> <span class="o">=</span> <span class="n">NamedValues</span><span class="p">[</span><span class="n">Name</span><span class="p">];</span>
+  <span class="k">return</span> <span class="n">V</span> <span class="o">?</span> <span class="n">V</span> <span class="o">:</span> <span class="n">ErrorV</span><span class="p">(</span><span class="s">"Unknown variable name"</span><span class="p">);</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>References to variables are also quite simple using LLVM. In the simple
+version of Kaleidoscope, we assume that the variable has already been
+emitted somewhere and its value is available. In practice, the only
+values that can be in the <tt class="docutils literal"><span class="pre">NamedValues</span></tt> map are function arguments.
+This code simply checks to see that the specified name is in the map (if
+not, an unknown variable is being referenced) and returns the value for
+it. In future chapters, we’ll add support for <a class="reference external" href="LangImpl5.html#for">loop induction
+variables</a> in the symbol table, and for <a class="reference external" href="LangImpl7.html#localvars">local
+variables</a>.</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="n">Value</span> <span class="o">*</span><span class="n">BinaryExprAST</span><span class="o">::</span><span class="n">Codegen</span><span class="p">()</span> <span class="p">{</span>
+  <span class="n">Value</span> <span class="o">*</span><span class="n">L</span> <span class="o">=</span> <span class="n">LHS</span><span class="o">-></span><span class="n">Codegen</span><span class="p">();</span>
+  <span class="n">Value</span> <span class="o">*</span><span class="n">R</span> <span class="o">=</span> <span class="n">RHS</span><span class="o">-></span><span class="n">Codegen</span><span class="p">();</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">L</span> <span class="o">==</span> <span class="mi">0</span> <span class="o">||</span> <span class="n">R</span> <span class="o">==</span> <span class="mi">0</span><span class="p">)</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+
+  <span class="k">switch</span> <span class="p">(</span><span class="n">Op</span><span class="p">)</span> <span class="p">{</span>
+  <span class="k">case</span> <span class="sc">'+'</span>: <span class="k">return</span> <span class="n">Builder</span><span class="p">.</span><span class="n">CreateFAdd</span><span class="p">(</span><span class="n">L</span><span class="p">,</span> <span class="n">R</span><span class="p">,</span> <span class="s">"addtmp"</span><span class="p">);</span>
+  <span class="k">case</span> <span class="sc">'-'</span>: <span class="k">return</span> <span class="n">Builder</span><span class="p">.</span><span class="n">CreateFSub</span><span class="p">(</span><span class="n">L</span><span class="p">,</span> <span class="n">R</span><span class="p">,</span> <span class="s">"subtmp"</span><span class="p">);</span>
+  <span class="k">case</span> <span class="sc">'*'</span>: <span class="k">return</span> <span class="n">Builder</span><span class="p">.</span><span class="n">CreateFMul</span><span class="p">(</span><span class="n">L</span><span class="p">,</span> <span class="n">R</span><span class="p">,</span> <span class="s">"multmp"</span><span class="p">);</span>
+  <span class="k">case</span> <span class="sc">'<'</span>:
+    <span class="n">L</span> <span class="o">=</span> <span class="n">Builder</span><span class="p">.</span><span class="n">CreateFCmpULT</span><span class="p">(</span><span class="n">L</span><span class="p">,</span> <span class="n">R</span><span class="p">,</span> <span class="s">"cmptmp"</span><span class="p">);</span>
+    <span class="c1">// Convert bool 0/1 to double 0.0 or 1.0</span>
+    <span class="k">return</span> <span class="n">Builder</span><span class="p">.</span><span class="n">CreateUIToFP</span><span class="p">(</span><span class="n">L</span><span class="p">,</span> <span class="n">Type</span><span class="o">::</span><span class="n">getDoubleTy</span><span class="p">(</span><span class="n">getGlobalContext</span><span class="p">()),</span>
+                                <span class="s">"booltmp"</span><span class="p">);</span>
+  <span class="nl">default:</span> <span class="k">return</span> <span class="nf">ErrorV</span><span class="p">(</span><span class="s">"invalid binary operator"</span><span class="p">);</span>
+  <span class="p">}</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>Binary operators start to get more interesting. The basic idea here is
+that we recursively emit code for the left-hand side of the expression,
+then the right-hand side, then we compute the result of the binary
+expression. In this code, we do a simple switch on the opcode to create
+the right LLVM instruction.</p>
+<p>In the example above, the LLVM builder class is starting to show its
+value. IRBuilder knows where to insert the newly created instruction,
+all you have to do is specify what instruction to create (e.g. with
+<tt class="docutils literal"><span class="pre">CreateFAdd</span></tt>), which operands to use (<tt class="docutils literal"><span class="pre">L</span></tt> and <tt class="docutils literal"><span class="pre">R</span></tt> here) and
+optionally provide a name for the generated instruction.</p>
+<p>One nice thing about LLVM is that the name is just a hint. For instance,
+if the code above emits multiple “addtmp” variables, LLVM will
+automatically provide each one with an increasing, unique numeric
+suffix. Local value names for instructions are purely optional, but it
+makes it much easier to read the IR dumps.</p>
+<p><a class="reference external" href="../LangRef.html#instref">LLVM instructions</a> are constrained by strict
+rules: for example, the Left and Right operators of an <a class="reference external" href="../LangRef.html#i_add">add
+instruction</a> must have the same type, and the
+result type of the add must match the operand types. Because all values
+in Kaleidoscope are doubles, this makes for very simple code for add,
+sub and mul.</p>
+<p>On the other hand, LLVM specifies that the <a class="reference external" href="../LangRef.html#i_fcmp">fcmp
+instruction</a> always returns an ‘i1’ value (a
+one bit integer). The problem with this is that Kaleidoscope wants the
+value to be a 0.0 or 1.0 value. In order to get these semantics, we
+combine the fcmp instruction with a <a class="reference external" href="../LangRef.html#i_uitofp">uitofp
+instruction</a>. This instruction converts its
+input integer into a floating point value by treating the input as an
+unsigned value. In contrast, if we used the <a class="reference external" href="../LangRef.html#i_sitofp">sitofp
+instruction</a>, the Kaleidoscope ‘<’ operator
+would return 0.0 and -1.0, depending on the input value.</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="n">Value</span> <span class="o">*</span><span class="n">CallExprAST</span><span class="o">::</span><span class="n">Codegen</span><span class="p">()</span> <span class="p">{</span>
+  <span class="c1">// Look up the name in the global module table.</span>
+  <span class="n">Function</span> <span class="o">*</span><span class="n">CalleeF</span> <span class="o">=</span> <span class="n">TheModule</span><span class="o">-></span><span class="n">getFunction</span><span class="p">(</span><span class="n">Callee</span><span class="p">);</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">CalleeF</span> <span class="o">==</span> <span class="mi">0</span><span class="p">)</span>
+    <span class="k">return</span> <span class="n">ErrorV</span><span class="p">(</span><span class="s">"Unknown function referenced"</span><span class="p">);</span>
+
+  <span class="c1">// If argument mismatch error.</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">CalleeF</span><span class="o">-></span><span class="n">arg_size</span><span class="p">()</span> <span class="o">!=</span> <span class="n">Args</span><span class="p">.</span><span class="n">size</span><span class="p">())</span>
+    <span class="k">return</span> <span class="n">ErrorV</span><span class="p">(</span><span class="s">"Incorrect # arguments passed"</span><span class="p">);</span>
+
+  <span class="n">std</span><span class="o">::</span><span class="n">vector</span><span class="o"><</span><span class="n">Value</span><span class="o">*></span> <span class="n">ArgsV</span><span class="p">;</span>
+  <span class="k">for</span> <span class="p">(</span><span class="kt">unsigned</span> <span class="n">i</span> <span class="o">=</span> <span class="mi">0</span><span class="p">,</span> <span class="n">e</span> <span class="o">=</span> <span class="n">Args</span><span class="p">.</span><span class="n">size</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="p">{</span>
+    <span class="n">ArgsV</span><span class="p">.</span><span class="n">push_back</span><span class="p">(</span><span class="n">Args</span><span class="p">[</span><span class="n">i</span><span class="p">]</span><span class="o">-></span><span class="n">Codegen</span><span class="p">());</span>
+    <span class="k">if</span> <span class="p">(</span><span class="n">ArgsV</span><span class="p">.</span><span class="n">back</span><span class="p">()</span> <span class="o">==</span> <span class="mi">0</span><span class="p">)</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+  <span class="p">}</span>
+
+  <span class="k">return</span> <span class="n">Builder</span><span class="p">.</span><span class="n">CreateCall</span><span class="p">(</span><span class="n">CalleeF</span><span class="p">,</span> <span class="n">ArgsV</span><span class="p">,</span> <span class="s">"calltmp"</span><span class="p">);</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>Code generation for function calls is quite straightforward with LLVM.
+The code above initially does a function name lookup in the LLVM
+Module’s symbol table. Recall that the LLVM Module is the container that
+holds all of the functions we are JIT’ing. By giving each function the
+same name as what the user specifies, we can use the LLVM symbol table
+to resolve function names for us.</p>
+<p>Once we have the function to call, we recursively codegen each argument
+that is to be passed in, and create an LLVM <a class="reference external" href="../LangRef.html#i_call">call
+instruction</a>. Note that LLVM uses the native C
+calling conventions by default, allowing these calls to also call into
+standard library functions like “sin” and “cos”, with no additional
+effort.</p>
+<p>This wraps up our handling of the four basic expressions that we have so
+far in Kaleidoscope. Feel free to go in and add some more. For example,
+by browsing the <a class="reference external" href="../LangRef.html">LLVM language reference</a> you’ll find
+several other interesting instructions that are really easy to plug into
+our basic framework.</p>
+</div>
+<div class="section" id="function-code-generation">
+<h2><a class="toc-backref" href="#id4">3.4. Function Code Generation</a><a class="headerlink" href="#function-code-generation" title="Permalink to this headline">¶</a></h2>
+<p>Code generation for prototypes and functions must handle a number of
+details, which make their code less beautiful than expression code
+generation, but allows us to illustrate some important points. First,
+lets talk about code generation for prototypes: they are used both for
+function bodies and external function declarations. The code starts
+with:</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="n">Function</span> <span class="o">*</span><span class="n">PrototypeAST</span><span class="o">::</span><span class="n">Codegen</span><span class="p">()</span> <span class="p">{</span>
+  <span class="c1">// Make the function type:  double(double,double) etc.</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">vector</span><span class="o"><</span><span class="n">Type</span><span class="o">*></span> <span class="n">Doubles</span><span class="p">(</span><span class="n">Args</span><span class="p">.</span><span class="n">size</span><span class="p">(),</span>
+                             <span class="n">Type</span><span class="o">::</span><span class="n">getDoubleTy</span><span class="p">(</span><span class="n">getGlobalContext</span><span class="p">()));</span>
+  <span class="n">FunctionType</span> <span class="o">*</span><span class="n">FT</span> <span class="o">=</span> <span class="n">FunctionType</span><span class="o">::</span><span class="n">get</span><span class="p">(</span><span class="n">Type</span><span class="o">::</span><span class="n">getDoubleTy</span><span class="p">(</span><span class="n">getGlobalContext</span><span class="p">()),</span>
+                                       <span class="n">Doubles</span><span class="p">,</span> <span class="nb">false</span><span class="p">);</span>
+
+  <span class="n">Function</span> <span class="o">*</span><span class="n">F</span> <span class="o">=</span> <span class="n">Function</span><span class="o">::</span><span class="n">Create</span><span class="p">(</span><span class="n">FT</span><span class="p">,</span> <span class="n">Function</span><span class="o">::</span><span class="n">ExternalLinkage</span><span class="p">,</span> <span class="n">Name</span><span class="p">,</span> <span class="n">TheModule</span><span class="p">);</span>
+</pre></div>
+</div>
+<p>This code packs a lot of power into a few lines. Note first that this
+function returns a “Function*” instead of a “Value*”. Because a
+“prototype” really talks about the external interface for a function
+(not the value computed by an expression), it makes sense for it to
+return the LLVM Function it corresponds to when codegen’d.</p>
+<p>The call to <tt class="docutils literal"><span class="pre">FunctionType::get</span></tt> creates the <tt class="docutils literal"><span class="pre">FunctionType</span></tt> that
+should be used for a given Prototype. Since all function arguments in
+Kaleidoscope are of type double, the first line creates a vector of “N”
+LLVM double types. It then uses the <tt class="docutils literal"><span class="pre">Functiontype::get</span></tt> method to
+create a function type that takes “N” doubles as arguments, returns one
+double as a result, and that is not vararg (the false parameter
+indicates this). Note that Types in LLVM are uniqued just like Constants
+are, so you don’t “new” a type, you “get” it.</p>
+<p>The final line above actually creates the function that the prototype
+will correspond to. This indicates the type, linkage and name to use, as
+well as which module to insert into. “<a class="reference external" href="../LangRef.html#linkage">external
+linkage</a>” means that the function may be
+defined outside the current module and/or that it is callable by
+functions outside the module. The Name passed in is the name the user
+specified: since “<tt class="docutils literal"><span class="pre">TheModule</span></tt>” is specified, this name is registered
+in “<tt class="docutils literal"><span class="pre">TheModule</span></tt>“s symbol table, which is used by the function call
+code above.</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">// If F conflicted, there was already something named 'Name'.  If it has a</span>
+<span class="c1">// body, don't allow redefinition or reextern.</span>
+<span class="k">if</span> <span class="p">(</span><span class="n">F</span><span class="o">-></span><span class="n">getName</span><span class="p">()</span> <span class="o">!=</span> <span class="n">Name</span><span class="p">)</span> <span class="p">{</span>
+  <span class="c1">// Delete the one we just made and get the existing one.</span>
+  <span class="n">F</span><span class="o">-></span><span class="n">eraseFromParent</span><span class="p">();</span>
+  <span class="n">F</span> <span class="o">=</span> <span class="n">TheModule</span><span class="o">-></span><span class="n">getFunction</span><span class="p">(</span><span class="n">Name</span><span class="p">);</span>
+</pre></div>
+</div>
+<p>The Module symbol table works just like the Function symbol table when
+it comes to name conflicts: if a new function is created with a name
+that was previously added to the symbol table, the new function will get
+implicitly renamed when added to the Module. The code above exploits
+this fact to determine if there was a previous definition of this
+function.</p>
+<p>In Kaleidoscope, I choose to allow redefinitions of functions in two
+cases: first, we want to allow ‘extern’ing a function more than once, as
+long as the prototypes for the externs match (since all arguments have
+the same type, we just have to check that the number of arguments
+match). Second, we want to allow ‘extern’ing a function and then
+defining a body for it. This is useful when defining mutually recursive
+functions.</p>
+<p>In order to implement this, the code above first checks to see if there
+is a collision on the name of the function. If so, it deletes the
+function we just created (by calling <tt class="docutils literal"><span class="pre">eraseFromParent</span></tt>) and then
+calling <tt class="docutils literal"><span class="pre">getFunction</span></tt> to get the existing function with the specified
+name. Note that many APIs in LLVM have “erase” forms and “remove” forms.
+The “remove” form unlinks the object from its parent (e.g. a Function
+from a Module) and returns it. The “erase” form unlinks the object and
+then deletes it.</p>
+<div class="highlight-c++"><div class="highlight"><pre>  <span class="c1">// If F already has a body, reject this.</span>
+  <span class="k">if</span> <span class="p">(</span><span class="o">!</span><span class="n">F</span><span class="o">-></span><span class="n">empty</span><span class="p">())</span> <span class="p">{</span>
+    <span class="n">ErrorF</span><span class="p">(</span><span class="s">"redefinition of function"</span><span class="p">);</span>
+    <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+  <span class="p">}</span>
+
+  <span class="c1">// If F took a different number of args, reject.</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">F</span><span class="o">-></span><span class="n">arg_size</span><span class="p">()</span> <span class="o">!=</span> <span class="n">Args</span><span class="p">.</span><span class="n">size</span><span class="p">())</span> <span class="p">{</span>
+    <span class="n">ErrorF</span><span class="p">(</span><span class="s">"redefinition of function with different # args"</span><span class="p">);</span>
+    <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+  <span class="p">}</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>In order to verify the logic above, we first check to see if the
+pre-existing function is “empty”. In this case, empty means that it has
+no basic blocks in it, which means it has no body. If it has no body, it
+is a forward declaration. Since we don’t allow anything after a full
+definition of the function, the code rejects this case. If the previous
+reference to a function was an ‘extern’, we simply verify that the
+number of arguments for that definition and this one match up. If not,
+we emit an error.</p>
+<div class="highlight-c++"><div class="highlight"><pre>  <span class="c1">// Set names for all arguments.</span>
+  <span class="kt">unsigned</span> <span class="n">Idx</span> <span class="o">=</span> <span class="mi">0</span><span class="p">;</span>
+  <span class="k">for</span> <span class="p">(</span><span class="n">Function</span><span class="o">::</span><span class="n">arg_iterator</span> <span class="n">AI</span> <span class="o">=</span> <span class="n">F</span><span class="o">-></span><span class="n">arg_begin</span><span class="p">();</span> <span class="n">Idx</span> <span class="o">!=</span> <span class="n">Args</span><span class="p">.</span><span class="n">size</span><span class="p">();</span>
+       <span class="o">++</span><span class="n">AI</span><span class="p">,</span> <span class="o">++</span><span class="n">Idx</span><span class="p">)</span> <span class="p">{</span>
+    <span class="n">AI</span><span class="o">-></span><span class="n">setName</span><span class="p">(</span><span class="n">Args</span><span class="p">[</span><span class="n">Idx</span><span class="p">]);</span>
+
+    <span class="c1">// Add arguments to variable symbol table.</span>
+    <span class="n">NamedValues</span><span class="p">[</span><span class="n">Args</span><span class="p">[</span><span class="n">Idx</span><span class="p">]]</span> <span class="o">=</span> <span class="n">AI</span><span class="p">;</span>
+  <span class="p">}</span>
+  <span class="k">return</span> <span class="n">F</span><span class="p">;</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>The last bit of code for prototypes loops over all of the arguments in
+the function, setting the name of the LLVM Argument objects to match,
+and registering the arguments in the <tt class="docutils literal"><span class="pre">NamedValues</span></tt> map for future use
+by the <tt class="docutils literal"><span class="pre">VariableExprAST</span></tt> AST node. Once this is set up, it returns the
+Function object to the caller. Note that we don’t check for conflicting
+argument names here (e.g. “extern foo(a b a)”). Doing so would be very
+straight-forward with the mechanics we have already used above.</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="n">Function</span> <span class="o">*</span><span class="n">FunctionAST</span><span class="o">::</span><span class="n">Codegen</span><span class="p">()</span> <span class="p">{</span>
+  <span class="n">NamedValues</span><span class="p">.</span><span class="n">clear</span><span class="p">();</span>
+
+  <span class="n">Function</span> <span class="o">*</span><span class="n">TheFunction</span> <span class="o">=</span> <span class="n">Proto</span><span class="o">-></span><span class="n">Codegen</span><span class="p">();</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">TheFunction</span> <span class="o">==</span> <span class="mi">0</span><span class="p">)</span>
+    <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+</pre></div>
+</div>
+<p>Code generation for function definitions starts out simply enough: we
+just codegen the prototype (Proto) and verify that it is ok. We then
+clear out the <tt class="docutils literal"><span class="pre">NamedValues</span></tt> map to make sure that there isn’t anything
+in it from the last function we compiled. Code generation of the
+prototype ensures that there is an LLVM Function object that is ready to
+go for us.</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="c1">// Create a new basic block to start insertion into.</span>
+<span class="n">BasicBlock</span> <span class="o">*</span><span class="n">BB</span> <span class="o">=</span> <span class="n">BasicBlock</span><span class="o">::</span><span class="n">Create</span><span class="p">(</span><span class="n">getGlobalContext</span><span class="p">(),</span> <span class="s">"entry"</span><span class="p">,</span> <span class="n">TheFunction</span><span class="p">);</span>
+<span class="n">Builder</span><span class="p">.</span><span class="n">SetInsertPoint</span><span class="p">(</span><span class="n">BB</span><span class="p">);</span>
+
+<span class="k">if</span> <span class="p">(</span><span class="n">Value</span> <span class="o">*</span><span class="n">RetVal</span> <span class="o">=</span> <span class="n">Body</span><span class="o">-></span><span class="n">Codegen</span><span class="p">())</span> <span class="p">{</span>
+</pre></div>
+</div>
+<p>Now we get to the point where the <tt class="docutils literal"><span class="pre">Builder</span></tt> is set up. The first line
+creates a new <a class="reference external" href="http://en.wikipedia.org/wiki/Basic_block">basic block</a>
+(named “entry”), which is inserted into <tt class="docutils literal"><span class="pre">TheFunction</span></tt>. The second line
+then tells the builder that new instructions should be inserted into the
+end of the new basic block. Basic blocks in LLVM are an important part
+of functions that define the <a class="reference external" href="http://en.wikipedia.org/wiki/Control_flow_graph">Control Flow
+Graph</a>. Since we
+don’t have any control flow, our functions will only contain one block
+at this point. We’ll fix this in <a class="reference external" href="LangImpl5.html">Chapter 5</a> :).</p>
+<div class="highlight-c++"><div class="highlight"><pre><span class="k">if</span> <span class="p">(</span><span class="n">Value</span> <span class="o">*</span><span class="n">RetVal</span> <span class="o">=</span> <span class="n">Body</span><span class="o">-></span><span class="n">Codegen</span><span class="p">())</span> <span class="p">{</span>
+  <span class="c1">// Finish off the function.</span>
+  <span class="n">Builder</span><span class="p">.</span><span class="n">CreateRet</span><span class="p">(</span><span class="n">RetVal</span><span class="p">);</span>
+
+  <span class="c1">// Validate the generated code, checking for consistency.</span>
+  <span class="n">verifyFunction</span><span class="p">(</span><span class="o">*</span><span class="n">TheFunction</span><span class="p">);</span>
+
+  <span class="k">return</span> <span class="n">TheFunction</span><span class="p">;</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>Once the insertion point is set up, we call the <tt class="docutils literal"><span class="pre">CodeGen()</span></tt> method for
+the root expression of the function. If no error happens, this emits
+code to compute the expression into the entry block and returns the
+value that was computed. Assuming no error, we then create an LLVM <a class="reference external" href="../LangRef.html#i_ret">ret
+instruction</a>, which completes the function.
+Once the function is built, we call <tt class="docutils literal"><span class="pre">verifyFunction</span></tt>, which is
+provided by LLVM. This function does a variety of consistency checks on
+the generated code, to determine if our compiler is doing everything
+right. Using this is important: it can catch a lot of bugs. Once the
+function is finished and validated, we return it.</p>
+<div class="highlight-c++"><div class="highlight"><pre>  <span class="c1">// Error reading body, remove function.</span>
+  <span class="n">TheFunction</span><span class="o">-></span><span class="n">eraseFromParent</span><span class="p">();</span>
+  <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p>The only piece left here is handling of the error case. For simplicity,
+we handle this by merely deleting the function we produced with the
+<tt class="docutils literal"><span class="pre">eraseFromParent</span></tt> method. This allows the user to redefine a function
+that they incorrectly typed in before: if we didn’t delete it, it would
+live in the symbol table, with a body, preventing future redefinition.</p>
+<p>This code does have a bug, though. Since the <tt class="docutils literal"><span class="pre">PrototypeAST::Codegen</span></tt>
+can return a previously defined forward declaration, our code can
+actually delete a forward declaration. There are a number of ways to fix
+this bug, see what you can come up with! Here is a testcase:</p>
+<div class="highlight-python"><pre>extern foo(a b);     # ok, defines foo.
+def foo(a b) c;      # error, 'c' is invalid.
+def bar() foo(1, 2); # error, unknown function "foo"</pre>
+</div>
+</div>
+<div class="section" id="driver-changes-and-closing-thoughts">
+<h2><a class="toc-backref" href="#id5">3.5. Driver Changes and Closing Thoughts</a><a class="headerlink" href="#driver-changes-and-closing-thoughts" title="Permalink to this headline">¶</a></h2>
+<p>For now, code generation to LLVM doesn’t really get us much, except that
+we can look at the pretty IR calls. The sample code inserts calls to
+Codegen into the “<tt class="docutils literal"><span class="pre">HandleDefinition</span></tt>”, “<tt class="docutils literal"><span class="pre">HandleExtern</span></tt>” etc
+functions, and then dumps out the LLVM IR. This gives a nice way to look
+at the LLVM IR for simple functions. For example:</p>
+<div class="highlight-python"><pre>ready> 4+5;
+Read top-level expression:
+define double @0() {
+entry:
+  ret double 9.000000e+00
+}</pre>
+</div>
+<p>Note how the parser turns the top-level expression into anonymous
+functions for us. This will be handy when we add <a class="reference external" href="LangImpl4.html#jit">JIT
+support</a> in the next chapter. Also note that the
+code is very literally transcribed, no optimizations are being performed
+except simple constant folding done by IRBuilder. We will <a class="reference external" href="LangImpl4.html#trivialconstfold">add
+optimizations</a> explicitly in the next
+chapter.</p>
+<div class="highlight-python"><pre>ready> def foo(a b) a*a + 2*a*b + b*b;
+Read function definition:
+define double @foo(double %a, double %b) {
+entry:
+  %multmp = fmul double %a, %a
+  %multmp1 = fmul double 2.000000e+00, %a
+  %multmp2 = fmul double %multmp1, %b
+  %addtmp = fadd double %multmp, %multmp2
+  %multmp3 = fmul double %b, %b
+  %addtmp4 = fadd double %addtmp, %multmp3
+  ret double %addtmp4
+}</pre>
+</div>
+<p>This shows some simple arithmetic. Notice the striking similarity to the
+LLVM builder calls that we use to create the instructions.</p>
+<div class="highlight-python"><pre>ready> def bar(a) foo(a, 4.0) + bar(31337);
+Read function definition:
+define double @bar(double %a) {
+entry:
+  %calltmp = call double @foo(double %a, double 4.000000e+00)
+  %calltmp1 = call double @bar(double 3.133700e+04)
+  %addtmp = fadd double %calltmp, %calltmp1
+  ret double %addtmp
+}</pre>
+</div>
+<p>This shows some function calls. Note that this function will take a long
+time to execute if you call it. In the future we’ll add conditional
+control flow to actually make recursion useful :).</p>
+<div class="highlight-python"><pre>ready> extern cos(x);
+Read extern:
+declare double @cos(double)
+
+ready> cos(1.234);
+Read top-level expression:
+define double @1() {
+entry:
+  %calltmp = call double @cos(double 1.234000e+00)
+  ret double %calltmp
+}</pre>
+</div>
+<p>This shows an extern for the libm “cos” function, and a call to it.</p>
+<div class="highlight-python"><pre>ready> ^D
+; ModuleID = 'my cool jit'
+
+define double @0() {
+entry:
+  %addtmp = fadd double 4.000000e+00, 5.000000e+00
+  ret double %addtmp
+}
+
+define double @foo(double %a, double %b) {
+entry:
+  %multmp = fmul double %a, %a
+  %multmp1 = fmul double 2.000000e+00, %a
+  %multmp2 = fmul double %multmp1, %b
+  %addtmp = fadd double %multmp, %multmp2
+  %multmp3 = fmul double %b, %b
+  %addtmp4 = fadd double %addtmp, %multmp3
+  ret double %addtmp4
+}
+
+define double @bar(double %a) {
+entry:
+  %calltmp = call double @foo(double %a, double 4.000000e+00)
+  %calltmp1 = call double @bar(double 3.133700e+04)
+  %addtmp = fadd double %calltmp, %calltmp1
+  ret double %addtmp
+}
+
+declare double @cos(double)
+
+define double @1() {
+entry:
+  %calltmp = call double @cos(double 1.234000e+00)
+  ret double %calltmp
+}</pre>
+</div>
+<p>When you quit the current demo, it dumps out the IR for the entire
+module generated. Here you can see the big picture with all the
+functions referencing each other.</p>
+<p>This wraps up the third chapter of the Kaleidoscope tutorial. Up next,
+we’ll describe how to <a class="reference external" href="LangImpl4.html">add JIT codegen and optimizer
+support</a> to this so we can actually start running
+code!</p>
+</div>
+<div class="section" id="full-code-listing">
+<h2><a class="toc-backref" href="#id6">3.6. 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, enhanced with
+the LLVM code generator. Because this uses the LLVM libraries, we need
+to link them in. To do this, we use the
+<a class="reference external" href="http://llvm.org/cmds/llvm-config.html">llvm-config</a> tool to inform
+our makefile/command line about which options to use:</p>
+<div class="highlight-bash"><div class="highlight"><pre><span class="c"># Compile</span>
+clang++ -g -O3 toy.cpp <span class="sb">`</span>llvm-config --cxxflags --ldflags --system-libs --libs core<span class="sb">`</span> -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="cp">#include "llvm/IR/Verifier.h"</span>
+<span class="cp">#include "llvm/IR/DerivedTypes.h"</span>
+<span class="cp">#include "llvm/IR/IRBuilder.h"</span>
+<span class="cp">#include "llvm/IR/LLVMContext.h"</span>
+<span class="cp">#include "llvm/IR/Module.h"</span>
+<span class="cp">#include <cctype></span>
+<span class="cp">#include <cstdio></span>
+<span class="cp">#include <map></span>
+<span class="cp">#include <string></span>
+<span class="cp">#include <vector></span>
+<span class="k">using</span> <span class="k">namespace</span> <span class="n">llvm</span><span class="p">;</span>
+
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+<span class="c1">// Lexer</span>
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+
+<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="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>
+
+<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>
+
+  <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>
+
+  <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>
+
+  <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>
+  
+  <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>
+
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+<span class="c1">// Abstract Syntax Tree (aka Parse Tree)</span>
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+<span class="k">namespace</span> <span class="p">{</span>
+<span class="c1">/// ExprAST - Base class for all expression nodes.</span>
+<span class="k">class</span> <span class="nc">ExprAST</span> <span class="p">{</span>
+<span class="nl">public:</span>
+  <span class="k">virtual</span> <span class="o">~</span><span class="n">ExprAST</span><span class="p">()</span> <span class="p">{}</span>
+  <span class="k">virtual</span> <span class="n">Value</span> <span class="o">*</span><span class="n">Codegen</span><span class="p">()</span> <span class="o">=</span> <span class="mi">0</span><span class="p">;</span>
+<span class="p">};</span>
+
+<span class="c1">/// NumberExprAST - Expression class for numeric literals like "1.0".</span>
+<span class="k">class</span> <span class="nc">NumberExprAST</span> <span class="o">:</span> <span class="k">public</span> <span class="n">ExprAST</span> <span class="p">{</span>
+  <span class="kt">double</span> <span class="n">Val</span><span class="p">;</span>
+<span class="nl">public:</span>
+  <span class="n">NumberExprAST</span><span class="p">(</span><span class="kt">double</span> <span class="n">val</span><span class="p">)</span> <span class="o">:</span> <span class="n">Val</span><span class="p">(</span><span class="n">val</span><span class="p">)</span> <span class="p">{}</span>
+  <span class="k">virtual</span> <span class="n">Value</span> <span class="o">*</span><span class="n">Codegen</span><span class="p">();</span>
+<span class="p">};</span>
+
+<span class="c1">/// VariableExprAST - Expression class for referencing a variable, like "a".</span>
+<span class="k">class</span> <span class="nc">VariableExprAST</span> <span class="o">:</span> <span class="k">public</span> <span class="n">ExprAST</span> <span class="p">{</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="nl">public:</span>
+  <span class="n">VariableExprAST</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="o">:</span> <span class="n">Name</span><span class="p">(</span><span class="n">name</span><span class="p">)</span> <span class="p">{}</span>
+  <span class="k">virtual</span> <span class="n">Value</span> <span class="o">*</span><span class="n">Codegen</span><span class="p">();</span>
+<span class="p">};</span>
+
+<span class="c1">/// BinaryExprAST - Expression class for a binary operator.</span>
+<span class="k">class</span> <span class="nc">BinaryExprAST</span> <span class="o">:</span> <span class="k">public</span> <span class="n">ExprAST</span> <span class="p">{</span>
+  <span class="kt">char</span> <span class="n">Op</span><span class="p">;</span>
+  <span class="n">ExprAST</span> <span class="o">*</span><span class="n">LHS</span><span class="p">,</span> <span class="o">*</span><span class="n">RHS</span><span class="p">;</span>
+<span class="nl">public:</span>
+  <span class="n">BinaryExprAST</span><span class="p">(</span><span class="kt">char</span> <span class="n">op</span><span class="p">,</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="n">lhs</span><span class="p">,</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="n">rhs</span><span class="p">)</span> 
+    <span class="o">:</span> <span class="n">Op</span><span class="p">(</span><span class="n">op</span><span class="p">),</span> <span class="n">LHS</span><span class="p">(</span><span class="n">lhs</span><span class="p">),</span> <span class="n">RHS</span><span class="p">(</span><span class="n">rhs</span><span class="p">)</span> <span class="p">{}</span>
+  <span class="k">virtual</span> <span class="n">Value</span> <span class="o">*</span><span class="n">Codegen</span><span class="p">();</span>
+<span class="p">};</span>
+
+<span class="c1">/// CallExprAST - Expression class for function calls.</span>
+<span class="k">class</span> <span class="nc">CallExprAST</span> <span class="o">:</span> <span class="k">public</span> <span class="n">ExprAST</span> <span class="p">{</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="n">Callee</span><span class="p">;</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">vector</span><span class="o"><</span><span class="n">ExprAST</span><span class="o">*></span> <span class="n">Args</span><span class="p">;</span>
+<span class="nl">public:</span>
+  <span class="n">CallExprAST</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">callee</span><span class="p">,</span> <span class="n">std</span><span class="o">::</span><span class="n">vector</span><span class="o"><</span><span class="n">ExprAST</span><span class="o">*></span> <span class="o">&</span><span class="n">args</span><span class="p">)</span>
+    <span class="o">:</span> <span class="n">Callee</span><span class="p">(</span><span class="n">callee</span><span class="p">),</span> <span class="n">Args</span><span class="p">(</span><span class="n">args</span><span class="p">)</span> <span class="p">{}</span>
+  <span class="k">virtual</span> <span class="n">Value</span> <span class="o">*</span><span class="n">Codegen</span><span class="p">();</span>
+<span class="p">};</span>
+
+<span class="c1">/// PrototypeAST - This class represents the "prototype" for a function,</span>
+<span class="c1">/// which captures its name, and its argument names (thus implicitly the number</span>
+<span class="c1">/// of arguments the function takes).</span>
+<span class="k">class</span> <span class="nc">PrototypeAST</span> <span class="p">{</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="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">string</span><span class="o">></span> <span class="n">Args</span><span class="p">;</span>
+<span class="nl">public:</span>
+  <span class="n">PrototypeAST</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="k">const</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">string</span><span class="o">></span> <span class="o">&</span><span class="n">args</span><span class="p">)</span>
+    <span class="o">:</span> <span class="n">Name</span><span class="p">(</span><span class="n">name</span><span class="p">),</span> <span class="n">Args</span><span class="p">(</span><span class="n">args</span><span class="p">)</span> <span class="p">{}</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">/// 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">PrototypeAST</span> <span class="o">*</span><span class="n">Proto</span><span class="p">;</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">PrototypeAST</span> <span class="o">*</span><span class="n">proto</span><span class="p">,</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">proto</span><span class="p">),</span> <span class="n">Body</span><span class="p">(</span><span class="n">body</span><span class="p">)</span> <span class="p">{}</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="p">}</span> <span class="c1">// end anonymous namespace</span>
+
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+<span class="c1">// Parser</span>
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+
+<span class="c1">/// CurTok/getNextToken - Provide a simple token buffer.  CurTok is the current</span>
+<span class="c1">/// token the parser is looking at.  getNextToken reads another token from the</span>
+<span class="c1">/// lexer and updates CurTok with its results.</span>
+<span class="k">static</span> <span class="kt">int</span> <span class="n">CurTok</span><span class="p">;</span>
+<span class="k">static</span> <span class="kt">int</span> <span class="nf">getNextToken</span><span class="p">()</span> <span class="p">{</span>
+  <span class="k">return</span> <span class="n">CurTok</span> <span class="o">=</span> <span class="n">gettok</span><span class="p">();</span>
+<span class="p">}</span>
+
+<span class="c1">/// BinopPrecedence - This holds the precedence for each binary operator that is</span>
+<span class="c1">/// defined.</span>
+<span class="k">static</span> <span class="n">std</span><span class="o">::</span><span class="n">map</span><span class="o"><</span><span class="kt">char</span><span class="p">,</span> <span class="kt">int</span><span class="o">></span> <span class="n">BinopPrecedence</span><span class="p">;</span>
+
+<span class="c1">/// GetTokPrecedence - Get the precedence of the pending binary operator token.</span>
+<span class="k">static</span> <span class="kt">int</span> <span class="nf">GetTokPrecedence</span><span class="p">()</span> <span class="p">{</span>
+  <span class="k">if</span> <span class="p">(</span><span class="o">!</span><span class="n">isascii</span><span class="p">(</span><span class="n">CurTok</span><span class="p">))</span>
+    <span class="k">return</span> <span class="o">-</span><span class="mi">1</span><span class="p">;</span>
+  
+  <span class="c1">// Make sure it's a declared binop.</span>
+  <span class="kt">int</span> <span class="n">TokPrec</span> <span class="o">=</span> <span class="n">BinopPrecedence</span><span class="p">[</span><span class="n">CurTok</span><span class="p">];</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">TokPrec</span> <span class="o"><=</span> <span class="mi">0</span><span class="p">)</span> <span class="k">return</span> <span class="o">-</span><span class="mi">1</span><span class="p">;</span>
+  <span class="k">return</span> <span class="n">TokPrec</span><span class="p">;</span>
+<span class="p">}</span>
+
+<span class="c1">/// Error* - These are little helper functions for error handling.</span>
+<span class="n">ExprAST</span> <span class="o">*</span><span class="nf">Error</span><span class="p">(</span><span class="k">const</span> <span class="kt">char</span> <span class="o">*</span><span class="n">Str</span><span class="p">)</span> <span class="p">{</span> <span class="n">fprintf</span><span class="p">(</span><span class="n">stderr</span><span class="p">,</span> <span class="s">"Error: %s</span><span class="se">\n</span><span class="s">"</span><span class="p">,</span> <span class="n">Str</span><span class="p">);</span><span class="k">return</span> <span class="mi">0</span><span class="p">;}</span>
+<span class="n">PrototypeAST</span> <span class="o">*</span><span class="nf">ErrorP</span><span class="p">(</span><span class="k">const</span> <span class="kt">char</span> <span class="o">*</span><span class="n">Str</span><span class="p">)</span> <span class="p">{</span> <span class="n">Error</span><span class="p">(</span><span class="n">Str</span><span class="p">);</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span> <span class="p">}</span>
+<span class="n">FunctionAST</span> <span class="o">*</span><span class="nf">ErrorF</span><span class="p">(</span><span class="k">const</span> <span class="kt">char</span> <span class="o">*</span><span class="n">Str</span><span class="p">)</span> <span class="p">{</span> <span class="n">Error</span><span class="p">(</span><span class="n">Str</span><span class="p">);</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span> <span class="p">}</span>
+
+<span class="k">static</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="nf">ParseExpression</span><span class="p">();</span>
+
+<span class="c1">/// identifierexpr</span>
+<span class="c1">///   ::= identifier</span>
+<span class="c1">///   ::= identifier '(' expression* ')'</span>
+<span class="k">static</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="nf">ParseIdentifierExpr</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">IdName</span> <span class="o">=</span> <span class="n">IdentifierStr</span><span class="p">;</span>
+  
+  <span class="n">getNextToken</span><span class="p">();</span>  <span class="c1">// eat identifier.</span>
+  
+  <span class="k">if</span> <span class="p">(</span><span class="n">CurTok</span> <span class="o">!=</span> <span class="sc">'('</span><span class="p">)</span> <span class="c1">// Simple variable ref.</span>
+    <span class="k">return</span> <span class="k">new</span> <span class="n">VariableExprAST</span><span class="p">(</span><span class="n">IdName</span><span class="p">);</span>
+  
+  <span class="c1">// Call.</span>
+  <span class="n">getNextToken</span><span class="p">();</span>  <span class="c1">// eat (</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">vector</span><span class="o"><</span><span class="n">ExprAST</span><span class="o">*></span> <span class="n">Args</span><span class="p">;</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">CurTok</span> <span class="o">!=</span> <span class="sc">')'</span><span class="p">)</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">ExprAST</span> <span class="o">*</span><span class="n">Arg</span> <span class="o">=</span> <span class="n">ParseExpression</span><span class="p">();</span>
+      <span class="k">if</span> <span class="p">(</span><span class="o">!</span><span class="n">Arg</span><span class="p">)</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+      <span class="n">Args</span><span class="p">.</span><span class="n">push_back</span><span class="p">(</span><span class="n">Arg</span><span class="p">);</span>
+
+      <span class="k">if</span> <span class="p">(</span><span class="n">CurTok</span> <span class="o">==</span> <span class="sc">')'</span><span class="p">)</span> <span class="k">break</span><span class="p">;</span>
+
+      <span class="k">if</span> <span class="p">(</span><span class="n">CurTok</span> <span class="o">!=</span> <span class="sc">','</span><span class="p">)</span>
+        <span class="k">return</span> <span class="n">Error</span><span class="p">(</span><span class="s">"Expected ')' or ',' in argument list"</span><span class="p">);</span>
+      <span class="n">getNextToken</span><span class="p">();</span>
+    <span class="p">}</span>
+  <span class="p">}</span>
+
+  <span class="c1">// Eat the ')'.</span>
+  <span class="n">getNextToken</span><span class="p">();</span>
+  
+  <span class="k">return</span> <span class="k">new</span> <span class="n">CallExprAST</span><span class="p">(</span><span class="n">IdName</span><span class="p">,</span> <span class="n">Args</span><span class="p">);</span>
+<span class="p">}</span>
+
+<span class="c1">/// numberexpr ::= number</span>
+<span class="k">static</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="nf">ParseNumberExpr</span><span class="p">()</span> <span class="p">{</span>
+  <span class="n">ExprAST</span> <span class="o">*</span><span class="n">Result</span> <span class="o">=</span> <span class="k">new</span> <span class="n">NumberExprAST</span><span class="p">(</span><span class="n">NumVal</span><span class="p">);</span>
+  <span class="n">getNextToken</span><span class="p">();</span> <span class="c1">// consume the number</span>
+  <span class="k">return</span> <span class="n">Result</span><span class="p">;</span>
+<span class="p">}</span>
+
+<span class="c1">/// parenexpr ::= '(' expression ')'</span>
+<span class="k">static</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="nf">ParseParenExpr</span><span class="p">()</span> <span class="p">{</span>
+  <span class="n">getNextToken</span><span class="p">();</span>  <span class="c1">// eat (.</span>
+  <span class="n">ExprAST</span> <span class="o">*</span><span class="n">V</span> <span class="o">=</span> <span class="n">ParseExpression</span><span class="p">();</span>
+  <span class="k">if</span> <span class="p">(</span><span class="o">!</span><span class="n">V</span><span class="p">)</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+  
+  <span class="k">if</span> <span class="p">(</span><span class="n">CurTok</span> <span class="o">!=</span> <span class="sc">')'</span><span class="p">)</span>
+    <span class="k">return</span> <span class="n">Error</span><span class="p">(</span><span class="s">"expected ')'"</span><span class="p">);</span>
+  <span class="n">getNextToken</span><span class="p">();</span>  <span class="c1">// eat ).</span>
+  <span class="k">return</span> <span class="n">V</span><span class="p">;</span>
+<span class="p">}</span>
+
+<span class="c1">/// primary</span>
+<span class="c1">///   ::= identifierexpr</span>
+<span class="c1">///   ::= numberexpr</span>
+<span class="c1">///   ::= parenexpr</span>
+<span class="k">static</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="nf">ParsePrimary</span><span class="p">()</span> <span class="p">{</span>
+  <span class="k">switch</span> <span class="p">(</span><span class="n">CurTok</span><span class="p">)</span> <span class="p">{</span>
+  <span class="nl">default:</span> <span class="k">return</span> <span class="n">Error</span><span class="p">(</span><span class="s">"unknown token when expecting an expression"</span><span class="p">);</span>
+  <span class="k">case</span> <span class="n">tok_identifier</span>: <span class="k">return</span> <span class="n">ParseIdentifierExpr</span><span class="p">();</span>
+  <span class="k">case</span> <span class="n">tok_number</span>:     <span class="k">return</span> <span class="n">ParseNumberExpr</span><span class="p">();</span>
+  <span class="k">case</span> <span class="sc">'('</span>:            <span class="k">return</span> <span class="n">ParseParenExpr</span><span class="p">();</span>
+  <span class="p">}</span>
+<span class="p">}</span>
+
+<span class="c1">/// binoprhs</span>
+<span class="c1">///   ::= ('+' primary)*</span>
+<span class="k">static</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="nf">ParseBinOpRHS</span><span class="p">(</span><span class="kt">int</span> <span class="n">ExprPrec</span><span class="p">,</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="n">LHS</span><span class="p">)</span> <span class="p">{</span>
+  <span class="c1">// If this is a binop, find its precedence.</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="kt">int</span> <span class="n">TokPrec</span> <span class="o">=</span> <span class="n">GetTokPrecedence</span><span class="p">();</span>
+    
+    <span class="c1">// If this is a binop that binds at least as tightly as the current binop,</span>
+    <span class="c1">// consume it, otherwise we are done.</span>
+    <span class="k">if</span> <span class="p">(</span><span class="n">TokPrec</span> <span class="o"><</span> <span class="n">ExprPrec</span><span class="p">)</span>
+      <span class="k">return</span> <span class="n">LHS</span><span class="p">;</span>
+    
+    <span class="c1">// Okay, we know this is a binop.</span>
+    <span class="kt">int</span> <span class="n">BinOp</span> <span class="o">=</span> <span class="n">CurTok</span><span class="p">;</span>
+    <span class="n">getNextToken</span><span class="p">();</span>  <span class="c1">// eat binop</span>
+    
+    <span class="c1">// Parse the primary expression after the binary operator.</span>
+    <span class="n">ExprAST</span> <span class="o">*</span><span class="n">RHS</span> <span class="o">=</span> <span class="n">ParsePrimary</span><span class="p">();</span>
+    <span class="k">if</span> <span class="p">(</span><span class="o">!</span><span class="n">RHS</span><span class="p">)</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+    
+    <span class="c1">// If BinOp binds less tightly with RHS than the operator after RHS, let</span>
+    <span class="c1">// the pending operator take RHS as its LHS.</span>
+    <span class="kt">int</span> <span class="n">NextPrec</span> <span class="o">=</span> <span class="n">GetTokPrecedence</span><span class="p">();</span>
+    <span class="k">if</span> <span class="p">(</span><span class="n">TokPrec</span> <span class="o"><</span> <span class="n">NextPrec</span><span class="p">)</span> <span class="p">{</span>
+      <span class="n">RHS</span> <span class="o">=</span> <span class="n">ParseBinOpRHS</span><span class="p">(</span><span class="n">TokPrec</span><span class="o">+</span><span class="mi">1</span><span class="p">,</span> <span class="n">RHS</span><span class="p">);</span>
+      <span class="k">if</span> <span class="p">(</span><span class="n">RHS</span> <span class="o">==</span> <span class="mi">0</span><span class="p">)</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+    <span class="p">}</span>
+    
+    <span class="c1">// Merge LHS/RHS.</span>
+    <span class="n">LHS</span> <span class="o">=</span> <span class="k">new</span> <span class="n">BinaryExprAST</span><span class="p">(</span><span class="n">BinOp</span><span class="p">,</span> <span class="n">LHS</span><span class="p">,</span> <span class="n">RHS</span><span class="p">);</span>
+  <span class="p">}</span>
+<span class="p">}</span>
+
+<span class="c1">/// expression</span>
+<span class="c1">///   ::= primary binoprhs</span>
+<span class="c1">///</span>
+<span class="k">static</span> <span class="n">ExprAST</span> <span class="o">*</span><span class="nf">ParseExpression</span><span class="p">()</span> <span class="p">{</span>
+  <span class="n">ExprAST</span> <span class="o">*</span><span class="n">LHS</span> <span class="o">=</span> <span class="n">ParsePrimary</span><span class="p">();</span>
+  <span class="k">if</span> <span class="p">(</span><span class="o">!</span><span class="n">LHS</span><span class="p">)</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+  
+  <span class="k">return</span> <span class="n">ParseBinOpRHS</span><span class="p">(</span><span class="mi">0</span><span class="p">,</span> <span class="n">LHS</span><span class="p">);</span>
+<span class="p">}</span>
+
+<span class="c1">/// prototype</span>
+<span class="c1">///   ::= id '(' id* ')'</span>
+<span class="k">static</span> <span class="n">PrototypeAST</span> <span class="o">*</span><span class="nf">ParsePrototype</span><span class="p">()</span> <span class="p">{</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">CurTok</span> <span class="o">!=</span> <span class="n">tok_identifier</span><span class="p">)</span>
+    <span class="k">return</span> <span class="n">ErrorP</span><span class="p">(</span><span class="s">"Expected function name in prototype"</span><span class="p">);</span>
+
+  <span class="n">std</span><span class="o">::</span><span class="n">string</span> <span class="n">FnName</span> <span class="o">=</span> <span class="n">IdentifierStr</span><span class="p">;</span>
+  <span class="n">getNextToken</span><span class="p">();</span>
+  
+  <span class="k">if</span> <span class="p">(</span><span class="n">CurTok</span> <span class="o">!=</span> <span class="sc">'('</span><span class="p">)</span>
+    <span class="k">return</span> <span class="n">ErrorP</span><span class="p">(</span><span class="s">"Expected '(' in prototype"</span><span class="p">);</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">string</span><span class="o">></span> <span class="n">ArgNames</span><span class="p">;</span>
+  <span class="k">while</span> <span class="p">(</span><span class="n">getNextToken</span><span class="p">()</span> <span class="o">==</span> <span class="n">tok_identifier</span><span class="p">)</span>
+    <span class="n">ArgNames</span><span class="p">.</span><span class="n">push_back</span><span class="p">(</span><span class="n">IdentifierStr</span><span class="p">);</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">CurTok</span> <span class="o">!=</span> <span class="sc">')'</span><span class="p">)</span>
+    <span class="k">return</span> <span class="n">ErrorP</span><span class="p">(</span><span class="s">"Expected ')' in prototype"</span><span class="p">);</span>
+  
+  <span class="c1">// success.</span>
+  <span class="n">getNextToken</span><span class="p">();</span>  <span class="c1">// eat ')'.</span>
+  
+  <span class="k">return</span> <span class="k">new</span> <span class="n">PrototypeAST</span><span class="p">(</span><span class="n">FnName</span><span class="p">,</span> <span class="n">ArgNames</span><span class="p">);</span>
+<span class="p">}</span>
+
+<span class="c1">/// definition ::= 'def' prototype expression</span>
+<span class="k">static</span> <span class="n">FunctionAST</span> <span class="o">*</span><span class="nf">ParseDefinition</span><span class="p">()</span> <span class="p">{</span>
+  <span class="n">getNextToken</span><span class="p">();</span>  <span class="c1">// eat def.</span>
+  <span class="n">PrototypeAST</span> <span class="o">*</span><span class="n">Proto</span> <span class="o">=</span> <span class="n">ParsePrototype</span><span class="p">();</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">Proto</span> <span class="o">==</span> <span class="mi">0</span><span class="p">)</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+
+  <span class="k">if</span> <span class="p">(</span><span class="n">ExprAST</span> <span class="o">*</span><span class="n">E</span> <span class="o">=</span> <span class="n">ParseExpression</span><span class="p">())</span>
+    <span class="k">return</span> <span class="k">new</span> <span class="n">FunctionAST</span><span class="p">(</span><span class="n">Proto</span><span class="p">,</span> <span class="n">E</span><span class="p">);</span>
+  <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+<span class="p">}</span>
+
+<span class="c1">/// toplevelexpr ::= expression</span>
+<span class="k">static</span> <span class="n">FunctionAST</span> <span class="o">*</span><span class="nf">ParseTopLevelExpr</span><span class="p">()</span> <span class="p">{</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">ExprAST</span> <span class="o">*</span><span class="n">E</span> <span class="o">=</span> <span class="n">ParseExpression</span><span class="p">())</span> <span class="p">{</span>
+    <span class="c1">// Make an anonymous proto.</span>
+    <span class="n">PrototypeAST</span> <span class="o">*</span><span class="n">Proto</span> <span class="o">=</span> <span class="k">new</span> <span class="n">PrototypeAST</span><span class="p">(</span><span class="s">""</span><span class="p">,</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">string</span><span class="o">></span><span class="p">());</span>
+    <span class="k">return</span> <span class="k">new</span> <span class="n">FunctionAST</span><span class="p">(</span><span class="n">Proto</span><span class="p">,</span> <span class="n">E</span><span class="p">);</span>
+  <span class="p">}</span>
+  <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+<span class="p">}</span>
+
+<span class="c1">/// external ::= 'extern' prototype</span>
+<span class="k">static</span> <span class="n">PrototypeAST</span> <span class="o">*</span><span class="nf">ParseExtern</span><span class="p">()</span> <span class="p">{</span>
+  <span class="n">getNextToken</span><span class="p">();</span>  <span class="c1">// eat extern.</span>
+  <span class="k">return</span> <span class="n">ParsePrototype</span><span class="p">();</span>
+<span class="p">}</span>
+
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+<span class="c1">// Code Generation</span>
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+
+<span class="k">static</span> <span class="n">Module</span> <span class="o">*</span><span class="n">TheModule</span><span class="p">;</span>
+<span class="k">static</span> <span class="n">IRBuilder</span><span class="o"><></span> <span class="n">Builder</span><span class="p">(</span><span class="n">getGlobalContext</span><span class="p">());</span>
+<span class="k">static</span> <span class="n">std</span><span class="o">::</span><span class="n">map</span><span class="o"><</span><span class="n">std</span><span class="o">::</span><span class="n">string</span><span class="p">,</span> <span class="n">Value</span><span class="o">*></span> <span class="n">NamedValues</span><span class="p">;</span>
+
+<span class="n">Value</span> <span class="o">*</span><span class="nf">ErrorV</span><span class="p">(</span><span class="k">const</span> <span class="kt">char</span> <span class="o">*</span><span class="n">Str</span><span class="p">)</span> <span class="p">{</span> <span class="n">Error</span><span class="p">(</span><span class="n">Str</span><span class="p">);</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span> <span class="p">}</span>
+
+<span class="n">Value</span> <span class="o">*</span><span class="n">NumberExprAST</span><span class="o">::</span><span class="n">Codegen</span><span class="p">()</span> <span class="p">{</span>
+  <span class="k">return</span> <span class="n">ConstantFP</span><span class="o">::</span><span class="n">get</span><span class="p">(</span><span class="n">getGlobalContext</span><span class="p">(),</span> <span class="n">APFloat</span><span class="p">(</span><span class="n">Val</span><span class="p">));</span>
+<span class="p">}</span>
+
+<span class="n">Value</span> <span class="o">*</span><span class="n">VariableExprAST</span><span class="o">::</span><span class="n">Codegen</span><span class="p">()</span> <span class="p">{</span>
+  <span class="c1">// Look this variable up in the function.</span>
+  <span class="n">Value</span> <span class="o">*</span><span class="n">V</span> <span class="o">=</span> <span class="n">NamedValues</span><span class="p">[</span><span class="n">Name</span><span class="p">];</span>
+  <span class="k">return</span> <span class="n">V</span> <span class="o">?</span> <span class="n">V</span> <span class="o">:</span> <span class="n">ErrorV</span><span class="p">(</span><span class="s">"Unknown variable name"</span><span class="p">);</span>
+<span class="p">}</span>
+
+<span class="n">Value</span> <span class="o">*</span><span class="n">BinaryExprAST</span><span class="o">::</span><span class="n">Codegen</span><span class="p">()</span> <span class="p">{</span>
+  <span class="n">Value</span> <span class="o">*</span><span class="n">L</span> <span class="o">=</span> <span class="n">LHS</span><span class="o">-></span><span class="n">Codegen</span><span class="p">();</span>
+  <span class="n">Value</span> <span class="o">*</span><span class="n">R</span> <span class="o">=</span> <span class="n">RHS</span><span class="o">-></span><span class="n">Codegen</span><span class="p">();</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">L</span> <span class="o">==</span> <span class="mi">0</span> <span class="o">||</span> <span class="n">R</span> <span class="o">==</span> <span class="mi">0</span><span class="p">)</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+  
+  <span class="k">switch</span> <span class="p">(</span><span class="n">Op</span><span class="p">)</span> <span class="p">{</span>
+  <span class="k">case</span> <span class="sc">'+'</span>: <span class="k">return</span> <span class="n">Builder</span><span class="p">.</span><span class="n">CreateFAdd</span><span class="p">(</span><span class="n">L</span><span class="p">,</span> <span class="n">R</span><span class="p">,</span> <span class="s">"addtmp"</span><span class="p">);</span>
+  <span class="k">case</span> <span class="sc">'-'</span>: <span class="k">return</span> <span class="n">Builder</span><span class="p">.</span><span class="n">CreateFSub</span><span class="p">(</span><span class="n">L</span><span class="p">,</span> <span class="n">R</span><span class="p">,</span> <span class="s">"subtmp"</span><span class="p">);</span>
+  <span class="k">case</span> <span class="sc">'*'</span>: <span class="k">return</span> <span class="n">Builder</span><span class="p">.</span><span class="n">CreateFMul</span><span class="p">(</span><span class="n">L</span><span class="p">,</span> <span class="n">R</span><span class="p">,</span> <span class="s">"multmp"</span><span class="p">);</span>
+  <span class="k">case</span> <span class="sc">'<'</span>:
+    <span class="n">L</span> <span class="o">=</span> <span class="n">Builder</span><span class="p">.</span><span class="n">CreateFCmpULT</span><span class="p">(</span><span class="n">L</span><span class="p">,</span> <span class="n">R</span><span class="p">,</span> <span class="s">"cmptmp"</span><span class="p">);</span>
+    <span class="c1">// Convert bool 0/1 to double 0.0 or 1.0</span>
+    <span class="k">return</span> <span class="n">Builder</span><span class="p">.</span><span class="n">CreateUIToFP</span><span class="p">(</span><span class="n">L</span><span class="p">,</span> <span class="n">Type</span><span class="o">::</span><span class="n">getDoubleTy</span><span class="p">(</span><span class="n">getGlobalContext</span><span class="p">()),</span>
+                                <span class="s">"booltmp"</span><span class="p">);</span>
+  <span class="nl">default:</span> <span class="k">return</span> <span class="nf">ErrorV</span><span class="p">(</span><span class="s">"invalid binary operator"</span><span class="p">);</span>
+  <span class="p">}</span>
+<span class="p">}</span>
+
+<span class="n">Value</span> <span class="o">*</span><span class="n">CallExprAST</span><span class="o">::</span><span class="n">Codegen</span><span class="p">()</span> <span class="p">{</span>
+  <span class="c1">// Look up the name in the global module table.</span>
+  <span class="n">Function</span> <span class="o">*</span><span class="n">CalleeF</span> <span class="o">=</span> <span class="n">TheModule</span><span class="o">-></span><span class="n">getFunction</span><span class="p">(</span><span class="n">Callee</span><span class="p">);</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">CalleeF</span> <span class="o">==</span> <span class="mi">0</span><span class="p">)</span>
+    <span class="k">return</span> <span class="n">ErrorV</span><span class="p">(</span><span class="s">"Unknown function referenced"</span><span class="p">);</span>
+  
+  <span class="c1">// If argument mismatch error.</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">CalleeF</span><span class="o">-></span><span class="n">arg_size</span><span class="p">()</span> <span class="o">!=</span> <span class="n">Args</span><span class="p">.</span><span class="n">size</span><span class="p">())</span>
+    <span class="k">return</span> <span class="n">ErrorV</span><span class="p">(</span><span class="s">"Incorrect # arguments passed"</span><span class="p">);</span>
+
+  <span class="n">std</span><span class="o">::</span><span class="n">vector</span><span class="o"><</span><span class="n">Value</span><span class="o">*></span> <span class="n">ArgsV</span><span class="p">;</span>
+  <span class="k">for</span> <span class="p">(</span><span class="kt">unsigned</span> <span class="n">i</span> <span class="o">=</span> <span class="mi">0</span><span class="p">,</span> <span class="n">e</span> <span class="o">=</span> <span class="n">Args</span><span class="p">.</span><span class="n">size</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="p">{</span>
+    <span class="n">ArgsV</span><span class="p">.</span><span class="n">push_back</span><span class="p">(</span><span class="n">Args</span><span class="p">[</span><span class="n">i</span><span class="p">]</span><span class="o">-></span><span class="n">Codegen</span><span class="p">());</span>
+    <span class="k">if</span> <span class="p">(</span><span class="n">ArgsV</span><span class="p">.</span><span class="n">back</span><span class="p">()</span> <span class="o">==</span> <span class="mi">0</span><span class="p">)</span> <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+  <span class="p">}</span>
+  
+  <span class="k">return</span> <span class="n">Builder</span><span class="p">.</span><span class="n">CreateCall</span><span class="p">(</span><span class="n">CalleeF</span><span class="p">,</span> <span class="n">ArgsV</span><span class="p">,</span> <span class="s">"calltmp"</span><span class="p">);</span>
+<span class="p">}</span>
+
+<span class="n">Function</span> <span class="o">*</span><span class="n">PrototypeAST</span><span class="o">::</span><span class="n">Codegen</span><span class="p">()</span> <span class="p">{</span>
+  <span class="c1">// Make the function type:  double(double,double) etc.</span>
+  <span class="n">std</span><span class="o">::</span><span class="n">vector</span><span class="o"><</span><span class="n">Type</span><span class="o">*></span> <span class="n">Doubles</span><span class="p">(</span><span class="n">Args</span><span class="p">.</span><span class="n">size</span><span class="p">(),</span>
+                             <span class="n">Type</span><span class="o">::</span><span class="n">getDoubleTy</span><span class="p">(</span><span class="n">getGlobalContext</span><span class="p">()));</span>
+  <span class="n">FunctionType</span> <span class="o">*</span><span class="n">FT</span> <span class="o">=</span> <span class="n">FunctionType</span><span class="o">::</span><span class="n">get</span><span class="p">(</span><span class="n">Type</span><span class="o">::</span><span class="n">getDoubleTy</span><span class="p">(</span><span class="n">getGlobalContext</span><span class="p">()),</span>
+                                       <span class="n">Doubles</span><span class="p">,</span> <span class="nb">false</span><span class="p">);</span>
+  
+  <span class="n">Function</span> <span class="o">*</span><span class="n">F</span> <span class="o">=</span> <span class="n">Function</span><span class="o">::</span><span class="n">Create</span><span class="p">(</span><span class="n">FT</span><span class="p">,</span> <span class="n">Function</span><span class="o">::</span><span class="n">ExternalLinkage</span><span class="p">,</span> <span class="n">Name</span><span class="p">,</span> <span class="n">TheModule</span><span class="p">);</span>
+  
+  <span class="c1">// If F conflicted, there was already something named 'Name'.  If it has a</span>
+  <span class="c1">// body, don't allow redefinition or reextern.</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">F</span><span class="o">-></span><span class="n">getName</span><span class="p">()</span> <span class="o">!=</span> <span class="n">Name</span><span class="p">)</span> <span class="p">{</span>
+    <span class="c1">// Delete the one we just made and get the existing one.</span>
+    <span class="n">F</span><span class="o">-></span><span class="n">eraseFromParent</span><span class="p">();</span>
+    <span class="n">F</span> <span class="o">=</span> <span class="n">TheModule</span><span class="o">-></span><span class="n">getFunction</span><span class="p">(</span><span class="n">Name</span><span class="p">);</span>
+    
+    <span class="c1">// If F already has a body, reject this.</span>
+    <span class="k">if</span> <span class="p">(</span><span class="o">!</span><span class="n">F</span><span class="o">-></span><span class="n">empty</span><span class="p">())</span> <span class="p">{</span>
+      <span class="n">ErrorF</span><span class="p">(</span><span class="s">"redefinition of function"</span><span class="p">);</span>
+      <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+    <span class="p">}</span>
+    
+    <span class="c1">// If F took a different number of args, reject.</span>
+    <span class="k">if</span> <span class="p">(</span><span class="n">F</span><span class="o">-></span><span class="n">arg_size</span><span class="p">()</span> <span class="o">!=</span> <span class="n">Args</span><span class="p">.</span><span class="n">size</span><span class="p">())</span> <span class="p">{</span>
+      <span class="n">ErrorF</span><span class="p">(</span><span class="s">"redefinition of function with different # args"</span><span class="p">);</span>
+      <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+    <span class="p">}</span>
+  <span class="p">}</span>
+  
+  <span class="c1">// Set names for all arguments.</span>
+  <span class="kt">unsigned</span> <span class="n">Idx</span> <span class="o">=</span> <span class="mi">0</span><span class="p">;</span>
+  <span class="k">for</span> <span class="p">(</span><span class="n">Function</span><span class="o">::</span><span class="n">arg_iterator</span> <span class="n">AI</span> <span class="o">=</span> <span class="n">F</span><span class="o">-></span><span class="n">arg_begin</span><span class="p">();</span> <span class="n">Idx</span> <span class="o">!=</span> <span class="n">Args</span><span class="p">.</span><span class="n">size</span><span class="p">();</span>
+       <span class="o">++</span><span class="n">AI</span><span class="p">,</span> <span class="o">++</span><span class="n">Idx</span><span class="p">)</span> <span class="p">{</span>
+    <span class="n">AI</span><span class="o">-></span><span class="n">setName</span><span class="p">(</span><span class="n">Args</span><span class="p">[</span><span class="n">Idx</span><span class="p">]);</span>
+    
+    <span class="c1">// Add arguments to variable symbol table.</span>
+    <span class="n">NamedValues</span><span class="p">[</span><span class="n">Args</span><span class="p">[</span><span class="n">Idx</span><span class="p">]]</span> <span class="o">=</span> <span class="n">AI</span><span class="p">;</span>
+  <span class="p">}</span>
+  
+  <span class="k">return</span> <span class="n">F</span><span class="p">;</span>
+<span class="p">}</span>
+
+<span class="n">Function</span> <span class="o">*</span><span class="n">FunctionAST</span><span class="o">::</span><span class="n">Codegen</span><span class="p">()</span> <span class="p">{</span>
+  <span class="n">NamedValues</span><span class="p">.</span><span class="n">clear</span><span class="p">();</span>
+  
+  <span class="n">Function</span> <span class="o">*</span><span class="n">TheFunction</span> <span class="o">=</span> <span class="n">Proto</span><span class="o">-></span><span class="n">Codegen</span><span class="p">();</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">TheFunction</span> <span class="o">==</span> <span class="mi">0</span><span class="p">)</span>
+    <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+  
+  <span class="c1">// Create a new basic block to start insertion into.</span>
+  <span class="n">BasicBlock</span> <span class="o">*</span><span class="n">BB</span> <span class="o">=</span> <span class="n">BasicBlock</span><span class="o">::</span><span class="n">Create</span><span class="p">(</span><span class="n">getGlobalContext</span><span class="p">(),</span> <span class="s">"entry"</span><span class="p">,</span> <span class="n">TheFunction</span><span class="p">);</span>
+  <span class="n">Builder</span><span class="p">.</span><span class="n">SetInsertPoint</span><span class="p">(</span><span class="n">BB</span><span class="p">);</span>
+  
+  <span class="k">if</span> <span class="p">(</span><span class="n">Value</span> <span class="o">*</span><span class="n">RetVal</span> <span class="o">=</span> <span class="n">Body</span><span class="o">-></span><span class="n">Codegen</span><span class="p">())</span> <span class="p">{</span>
+    <span class="c1">// Finish off the function.</span>
+    <span class="n">Builder</span><span class="p">.</span><span class="n">CreateRet</span><span class="p">(</span><span class="n">RetVal</span><span class="p">);</span>
+
+    <span class="c1">// Validate the generated code, checking for consistency.</span>
+    <span class="n">verifyFunction</span><span class="p">(</span><span class="o">*</span><span class="n">TheFunction</span><span class="p">);</span>
+
+    <span class="k">return</span> <span class="n">TheFunction</span><span class="p">;</span>
+  <span class="p">}</span>
+  
+  <span class="c1">// Error reading body, remove function.</span>
+  <span class="n">TheFunction</span><span class="o">-></span><span class="n">eraseFromParent</span><span class="p">();</span>
+  <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+<span class="p">}</span>
+
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+<span class="c1">// Top-Level parsing and JIT Driver</span>
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+
+<span class="k">static</span> <span class="kt">void</span> <span class="n">HandleDefinition</span><span class="p">()</span> <span class="p">{</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">FunctionAST</span> <span class="o">*</span><span class="n">F</span> <span class="o">=</span> <span class="n">ParseDefinition</span><span class="p">())</span> <span class="p">{</span>
+    <span class="k">if</span> <span class="p">(</span><span class="n">Function</span> <span class="o">*</span><span class="n">LF</span> <span class="o">=</span> <span class="n">F</span><span class="o">-></span><span class="n">Codegen</span><span class="p">())</span> <span class="p">{</span>
+      <span class="n">fprintf</span><span class="p">(</span><span class="n">stderr</span><span class="p">,</span> <span class="s">"Read function definition:"</span><span class="p">);</span>
+      <span class="n">LF</span><span class="o">-></span><span class="n">dump</span><span class="p">();</span>
+    <span class="p">}</span>
+  <span class="p">}</span> <span class="k">else</span> <span class="p">{</span>
+    <span class="c1">// Skip token for error recovery.</span>
+    <span class="n">getNextToken</span><span class="p">();</span>
+  <span class="p">}</span>
+<span class="p">}</span>
+
+<span class="k">static</span> <span class="kt">void</span> <span class="n">HandleExtern</span><span class="p">()</span> <span class="p">{</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">PrototypeAST</span> <span class="o">*</span><span class="n">P</span> <span class="o">=</span> <span class="n">ParseExtern</span><span class="p">())</span> <span class="p">{</span>
+    <span class="k">if</span> <span class="p">(</span><span class="n">Function</span> <span class="o">*</span><span class="n">F</span> <span class="o">=</span> <span class="n">P</span><span class="o">-></span><span class="n">Codegen</span><span class="p">())</span> <span class="p">{</span>
+      <span class="n">fprintf</span><span class="p">(</span><span class="n">stderr</span><span class="p">,</span> <span class="s">"Read extern: "</span><span class="p">);</span>
+      <span class="n">F</span><span class="o">-></span><span class="n">dump</span><span class="p">();</span>
+    <span class="p">}</span>
+  <span class="p">}</span> <span class="k">else</span> <span class="p">{</span>
+    <span class="c1">// Skip token for error recovery.</span>
+    <span class="n">getNextToken</span><span class="p">();</span>
+  <span class="p">}</span>
+<span class="p">}</span>
+
+<span class="k">static</span> <span class="kt">void</span> <span class="n">HandleTopLevelExpression</span><span class="p">()</span> <span class="p">{</span>
+  <span class="c1">// Evaluate a top-level expression into an anonymous function.</span>
+  <span class="k">if</span> <span class="p">(</span><span class="n">FunctionAST</span> <span class="o">*</span><span class="n">F</span> <span class="o">=</span> <span class="n">ParseTopLevelExpr</span><span class="p">())</span> <span class="p">{</span>
+    <span class="k">if</span> <span class="p">(</span><span class="n">Function</span> <span class="o">*</span><span class="n">LF</span> <span class="o">=</span> <span class="n">F</span><span class="o">-></span><span class="n">Codegen</span><span class="p">())</span> <span class="p">{</span>
+      <span class="n">fprintf</span><span class="p">(</span><span class="n">stderr</span><span class="p">,</span> <span class="s">"Read top-level expression:"</span><span class="p">);</span>
+      <span class="n">LF</span><span class="o">-></span><span class="n">dump</span><span class="p">();</span>
+    <span class="p">}</span>
+  <span class="p">}</span> <span class="k">else</span> <span class="p">{</span>
+    <span class="c1">// Skip token for error recovery.</span>
+    <span class="n">getNextToken</span><span class="p">();</span>
+  <span class="p">}</span>
+<span class="p">}</span>
+
+<span class="c1">/// top ::= definition | external | expression | ';'</span>
+<span class="k">static</span> <span class="kt">void</span> <span class="n">MainLoop</span><span class="p">()</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">fprintf</span><span class="p">(</span><span class="n">stderr</span><span class="p">,</span> <span class="s">"ready> "</span><span class="p">);</span>
+    <span class="k">switch</span> <span class="p">(</span><span class="n">CurTok</span><span class="p">)</span> <span class="p">{</span>
+    <span class="k">case</span> <span class="n">tok_eof</span>:    <span class="k">return</span><span class="p">;</span>
+    <span class="k">case</span> <span class="sc">';'</span>:        <span class="n">getNextToken</span><span class="p">();</span> <span class="k">break</span><span class="p">;</span>  <span class="c1">// ignore top-level semicolons.</span>
+    <span class="k">case</span> <span class="n">tok_def</span>:    <span class="n">HandleDefinition</span><span class="p">();</span> <span class="k">break</span><span class="p">;</span>
+    <span class="k">case</span> <span class="n">tok_extern</span>: <span class="n">HandleExtern</span><span class="p">();</span> <span class="k">break</span><span class="p">;</span>
+    <span class="nl">default:</span>         <span class="n">HandleTopLevelExpression</span><span class="p">();</span> <span class="k">break</span><span class="p">;</span>
+    <span class="p">}</span>
+  <span class="p">}</span>
+<span class="p">}</span>
+
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+<span class="c1">// "Library" functions that can be "extern'd" from user code.</span>
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+
+<span class="c1">/// putchard - putchar that takes a double and returns 0.</span>
+<span class="k">extern</span> <span class="s">"C"</span> 
+<span class="kt">double</span> <span class="n">putchard</span><span class="p">(</span><span class="kt">double</span> <span class="n">X</span><span class="p">)</span> <span class="p">{</span>
+  <span class="n">putchar</span><span class="p">((</span><span class="kt">char</span><span class="p">)</span><span class="n">X</span><span class="p">);</span>
+  <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+<span class="p">}</span>
+
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+<span class="c1">// Main driver code.</span>
+<span class="c1">//===----------------------------------------------------------------------===//</span>
+
+<span class="kt">int</span> <span class="n">main</span><span class="p">()</span> <span class="p">{</span>
+  <span class="n">LLVMContext</span> <span class="o">&</span><span class="n">Context</span> <span class="o">=</span> <span class="n">getGlobalContext</span><span class="p">();</span>
+
+  <span class="c1">// Install standard binary operators.</span>
+  <span class="c1">// 1 is lowest precedence.</span>
+  <span class="n">BinopPrecedence</span><span class="p">[</span><span class="sc">'<'</span><span class="p">]</span> <span class="o">=</span> <span class="mi">10</span><span class="p">;</span>
+  <span class="n">BinopPrecedence</span><span class="p">[</span><span class="sc">'+'</span><span class="p">]</span> <span class="o">=</span> <span class="mi">20</span><span class="p">;</span>
+  <span class="n">BinopPrecedence</span><span class="p">[</span><span class="sc">'-'</span><span class="p">]</span> <span class="o">=</span> <span class="mi">20</span><span class="p">;</span>
+  <span class="n">BinopPrecedence</span><span class="p">[</span><span class="sc">'*'</span><span class="p">]</span> <span class="o">=</span> <span class="mi">40</span><span class="p">;</span>  <span class="c1">// highest.</span>
+
+  <span class="c1">// Prime the first token.</span>
+  <span class="n">fprintf</span><span class="p">(</span><span class="n">stderr</span><span class="p">,</span> <span class="s">"ready> "</span><span class="p">);</span>
+  <span class="n">getNextToken</span><span class="p">();</span>
+
+  <span class="c1">// Make the module, which holds all the code.</span>
+  <span class="n">TheModule</span> <span class="o">=</span> <span class="k">new</span> <span class="n">Module</span><span class="p">(</span><span class="s">"my cool jit"</span><span class="p">,</span> <span class="n">Context</span><span class="p">);</span>
+
+  <span class="c1">// Run the main "interpreter loop" now.</span>
+  <span class="n">MainLoop</span><span class="p">();</span>
+
+  <span class="c1">// Print out all of the generated code.</span>
+  <span class="n">TheModule</span><span class="o">-></span><span class="n">dump</span><span class="p">();</span>
+
+  <span class="k">return</span> <span class="mi">0</span><span class="p">;</span>
+<span class="p">}</span>
+</pre></div>
+</div>
+<p><a class="reference external" href="LangImpl4.html">Next: Adding JIT and Optimizer Support</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="LangImpl4.html" title="4. Kaleidoscope: Adding JIT and Optimizer Support"
+             >next</a> |</li>
+        <li class="right" >
+          <a href="LangImpl2.html" title="2. Kaleidoscope: Implementing a Parser and AST"
+             >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-2014, LLVM Project.
+      Last updated on 2015-05-25.
+      Created using <a href="http://sphinx.pocoo.org/">Sphinx</a> 1.1.3.
+    </div>
+  </body>
+</html>
\ No newline at end of file






More information about the llvm-commits mailing list