Annotation of gforth/doc/vmgen.texi, revision 1.3

1.1       anton       1: @include version.texi
                      2: 
                      3: @c @ifnottex
                      4: This file documents vmgen (Gforth @value{VERSION}).
                      5: 
1.2       anton       6: @chapter Introduction
1.1       anton       7: 
                      8: Vmgen is a tool for writing efficient interpreters.  It takes a simple
                      9: virtual machine description and generates efficient C code for dealing
                     10: with the virtual machine code in various ways (in particular, executing
                     11: it).  The run-time efficiency of the resulting interpreters is usually
                     12: within a factor of 10 of machine code produced by an optimizing
                     13: compiler.
                     14: 
                     15: The interpreter design strategy supported by vmgen is to divide the
                     16: interpreter into two parts:
                     17: 
                     18: @itemize @bullet
                     19: 
                     20: @item The @emph{front end} takes the source code of the language to be
                     21: implemented, and translates it into virtual machine code.  This is
                     22: similar to an ordinary compiler front end; typically an interpreter
                     23: front-end performs no optimization, so it is relatively simple to
                     24: implement and runs fast.
                     25: 
                     26: @item The @emph{virtual machine interpreter} executes the virtual
                     27: machine code.
                     28: 
                     29: @end itemize
                     30: 
                     31: Such a division is usually used in interpreters, for modularity as well
                     32: as for efficiency reasons.  The virtual machine code is typically passed
                     33: between front end and virtual machine interpreter in memory, like in a
                     34: load-and-go compiler; this avoids the complexity and time cost of
                     35: writing the code to a file and reading it again.
                     36: 
                     37: A @emph{virtual machine} (VM) represents the program as a sequence of
                     38: @emph{VM instructions}, following each other in memory, similar to real
                     39: machine code.  Control flow occurs through VM branch instructions, like
                     40: in a real machine.
                     41: 
                     42: In this setup, vmgen can generate most of the code dealing with virtual
                     43: machine instructions from a simple description of the virtual machine
                     44: instructions (@pxref...), in particular:
                     45: 
                     46: @table @emph
                     47: 
                     48: @item VM instruction execution
                     49: 
                     50: @item VM code generation
                     51: Useful in the front end.
                     52: 
                     53: @item VM code decompiler
                     54: Useful for debugging the front end.
                     55: 
                     56: @item VM code tracing
                     57: Useful for debugging the front end and the VM interpreter.  You will
                     58: typically provide other means for debugging the user's programs at the
                     59: source level.
                     60: 
                     61: @item VM code profiling
                     62: Useful for optimizing the VM insterpreter with superinstructions
                     63: (@pxref...).
                     64: 
                     65: @end table
                     66: 
                     67: VMgen supports efficient interpreters though various optimizations, in
                     68: particular
                     69: 
                     70: @itemize
                     71: 
                     72: @item Threaded code
                     73: 
                     74: @item Caching the top-of-stack in a register
                     75: 
                     76: @item Combining VM instructions into superinstructions
                     77: 
                     78: @item
                     79: Replicating VM (super)instructions for better BTB prediction accuracy
                     80: (not yet in vmgen-ex, but already in Gforth).
                     81: 
                     82: @end itemize
                     83: 
                     84: As a result, vmgen-based interpreters are only about an order of
                     85: magintude slower than native code from an optimizing C compiler on small
                     86: benchmarks; on large benchmarks, which spend more time in the run-time
1.2       anton      87: system, the slowdown is often less (e.g., the slowdown of a
                     88: Vmgen-generated JVM interpreter over the best JVM JIT compiler we
                     89: measured is only a factor of 2-3 for large benchmarks; some other JITs
                     90: and all other interpreters we looked at were slower than our
                     91: interpreter).
1.1       anton      92: 
                     93: VMs are usually designed as stack machines (passing data between VM
                     94: instructions on a stack), and vmgen supports such designs especially
                     95: well; however, you can also use vmgen for implementing a register VM and
                     96: still benefit from most of the advantages offered by vmgen.
                     97: 
1.2       anton      98: There are many potential uses of the instruction descriptions that are
                     99: not implemented at the moment, but we are open for feature requests, and
                    100: we will implement new features if someone asks for them; so the feature
                    101: list above is not exhaustive.
1.1       anton     102: 
1.2       anton     103: @c *********************************************************************
                    104: @chapter Why interpreters?
                    105: 
                    106: Interpreters are a popular language implementation technique because
                    107: they combine all three of the following advantages:
                    108: 
                    109: @itemize
                    110: 
                    111: @item Ease of implementation
                    112: 
                    113: @item Portability
                    114: 
                    115: @item Fast edit-compile-run cycle
                    116: 
                    117: @end itemize
                    118: 
                    119: The main disadvantage of interpreters is their run-time speed.  However,
                    120: there are huge differences between different interpreters in this area:
                    121: the slowdown over optimized C code on programs consisting of simple
                    122: operations is typically a factor of 10 for the more efficient
                    123: interpreters, and a factor of 1000 for the less efficient ones (the
                    124: slowdown for programs executing complex operations is less, because the
                    125: time spent in libraries for executing complex operations is the same in
                    126: all implementation strategies).
                    127: 
                    128: Vmgen makes it even easier to implement interpreters.  It also supports
                    129: techniques for building efficient interpreters.
                    130: 
                    131: @c ********************************************************************
                    132: 
                    133: @chapter Concepts
                    134: 
                    135: @c --------------------------------------------------------------------
                    136: @section Front-end and virtual machine interpreter
                    137: 
                    138: @cindex front-end
                    139: Interpretive systems are typically divided into a @emph{front end} that
                    140: parses the input language and produces an intermediate representation
                    141: for the program, and an interpreter that executes the intermediate
                    142: representation of the program.
                    143: 
                    144: @cindex virtual machine
                    145: @cindex VM
                    146: @cindex instruction, VM
                    147: For efficient interpreters the intermediate representation of choice is
                    148: virtual machine code (rather than, e.g., an abstract syntax tree).
                    149: @emph{Virtual machine} (VM) code consists of VM instructions arranged
                    150: sequentially in memory; they are executed in sequence by the VM
                    151: interpreter, except for VM branch instructions, which implement control
                    152: structures.  The conceptual similarity to real machine code results in
                    153: the name @emph{virtual machine}.
                    154: 
                    155: In this framework, vmgen supports building the VM interpreter and any
                    156: other component dealing with VM instructions.  It does not have any
                    157: support for the front end, apart from VM code generation support.  The
                    158: front end can be implemented with classical compiler front-end
1.3     ! anton     159: techniques, supported by tools like @command{flex} and @command{bison}.
1.2       anton     160: 
                    161: The intermediate representation is usually just internal to the
                    162: interpreter, but some systems also support saving it to a file, either
                    163: as an image file, or in a full-blown linkable file format (e.g., JVM).
                    164: Vmgen currently has no special support for such features, but the
                    165: information in the instruction descriptions can be helpful, and we are
                    166: open for feature requests and suggestions.
1.3     ! anton     167: 
        !           168: @section Data handling
        !           169: 
        !           170: @cindex stack machine
        !           171: @cindex register machine
        !           172: Most VMs use one or more stacks for passing temporary data between VM
        !           173: instructions.  Another option is to use a register machine architecture
        !           174: for the virtual machine; however, this option is either slower or
        !           175: significantly more complex to implement than a stack machine architecture.
        !           176: 
        !           177: Vmgen has special support and optimizations for stack VMs, making their
        !           178: implementation easy and efficient.
        !           179: 
        !           180: You can also implement a register VM with vmgen (@pxref{Register
        !           181: Machines}), and you will still profit from most vmgen features.
        !           182: 
        !           183: @cindex stack item size
        !           184: @cindex size, stack items
        !           185: Stack items all have the same size, so they typically will be as wide as
        !           186: an integer, pointer, or floating-point value.  Vmgen supports treating
        !           187: two consecutive stack items as a single value, but anything larger is
        !           188: best kept in some other memory area (e.g., the heap), with pointers to
        !           189: the data on the stack.
        !           190: 
        !           191: @cindex instruction stream
        !           192: @cindex immediate arguments
        !           193: Another source of data is immediate arguments VM instructions (in the VM
        !           194: instruction stream).  The VM instruction stream is handled similar to a
        !           195: stack in vmgen.
        !           196: 
        !           197: @cindex garbage collection
        !           198: @cindex reference counting
        !           199: Vmgen has no built-in support for nor restrictions against @emph{garbage
        !           200: collection}.  If you need garbage collection, you need to provide it in
        !           201: your run-time libraries.  Using @emph{reference counting} is probably
        !           202: harder, but might be possible (contact us if you are interested).
        !           203: @c reference counting might be possible by including counting code in 
        !           204: @c the conversion macros.
        !           205: 
        !           206: @c *************************************************************
        !           207: @chapter Invoking vmgen
        !           208: 
        !           209: The usual way to invoke vmgen is as follows:
        !           210: 
        !           211: @example
        !           212: vmgen @var{infile}
        !           213: @end example
        !           214: 
        !           215: Here @var{infile} is the VM instruction description file, which usually
        !           216: ends in @file{.vmg}.  The output filenames are made by taking the
        !           217: basename of @file{infile} (i.e., the output files will be created in the
        !           218: current working directory) and replacing @file{.vmg} with @file{-vm.i},
        !           219: @file{-disasm.i}, @file{-gen.i}, @file{-labels.i}, @file{-profile.i},
        !           220: and @file{-peephole.i}.  E.g., @command{bison hack/foo.vmg} will create
        !           221: @file{foo-vm.i} etc.
        !           222: 
        !           223: The command-line options supported by vmgen are
        !           224: 
        !           225: @table @option
        !           226: 
        !           227: @cindex -h, command-line option
        !           228: @cindex --help, command-line option
        !           229: @item --help
        !           230: @itemx -h
        !           231: Print a message about the command-line options
        !           232: 
        !           233: @cindex -v, command-line option
        !           234: @cindex --version, command-line option
        !           235: @item --version
        !           236: @itemx -v
        !           237: Print version and exit
        !           238: @end table
        !           239: 
        !           240: @c env vars GFORTHDIR GFORTHDATADIR
        !           241: 
        !           242: @c ***************************************************************
        !           243: @chapter Input File Format
        !           244: 
        !           245: Vmgen takes as input a file containing specifications of virtual machine
        !           246: instructions.  This file usually has a name ending in @file{.vmg}.
        !           247: 
        !           248: The examples are taken from the example in @file{vmgen-ex}.
        !           249: 
        !           250: @section Input File Grammar
        !           251: 
        !           252: The grammar is in EBNF format, with @code{@var{a}|@var{b}} meaning
        !           253: ``@var{a} or @var{b}'', @code{@{@var{c}@}} meaning 0 or more repetitions
        !           254: of @var{c} and @code{[@var{d}]} meaning 0 or 1 repetitions of @var{d}.
        !           255: 
        !           256: Vmgen input is not free-format, so you have to take care where you put
        !           257: spaces and especially newlines; it's not as bad as makefiles, though:
        !           258: any sequence of spaces and tabs is equivalent to a single space.
        !           259: 
        !           260: @example
        !           261: description: {instruction|comment|eval-escape}
        !           262: 
        !           263: instruction: simple-inst|superinst
        !           264: 
        !           265: simple-inst: ident " (" stack-effect " )" newline c-code newline newline
        !           266: 
        !           267: stack-effect: {ident} " --" {ident}
        !           268: 
        !           269: super-inst: ident " =" ident {ident}  
        !           270: 
        !           271: comment:      "\ "  text newline
        !           272: 
        !           273: eval-escape:  "\e " text newline
        !           274: @end example
        !           275: @c \+ \- \g \f \c
        !           276: 
        !           277: Note that the @code{\}s in this grammar are meant literally, not as
        !           278: C-style encodings for no-printable characters.
        !           279: 
        !           280: The C code in @code{simple-inst} must not contain empty lines (because
        !           281: vmgen would mistake that as the end of the simple-inst.  The text in
        !           282: @code{comment} and @code{eval-escape} must not contain a newline.
        !           283: @code{Ident} must conform to the usual conventions of C identifiers
        !           284: (otherwise the C compiler would choke on the vmgen output).
        !           285: 
        !           286: Vmgen understands a few extensions beyond the grammar given here, but
        !           287: these extensions are only useful for building Gforth.  You can find a
        !           288: description of the format used for Gforth in @file{prim}.
        !           289: 
        !           290: @subsection
        !           291: @c woanders?
        !           292: The text in @code{eval-escape} is Forth code that is evaluated when
        !           293: vmgen reads the line.  If you do not know (and do not want to learn)
        !           294: Forth, you can build the text according to the following grammar; these
        !           295: rules are normally all Forth you need for using vmgen:
        !           296: 
        !           297: @example
        !           298: text: stack-decl|type-prefix-decl|stack-prefix-decl
        !           299: 
        !           300: stack-decl: "stack " ident ident ident
        !           301: type-prefix-decl: 
        !           302:     's" ' string '" ' ("single"|"double") ident "type-prefix" ident
        !           303: stack-prefix-decl:  ident "stack-prefix" string
        !           304: @end example
        !           305: 
        !           306: Note that the syntax of this code is not checked thoroughly (there are
        !           307: many other Forth program fragments that could be written there).
        !           308: 
        !           309: If you know Forth, the stack effects of the non-standard words involved
        !           310: are:
        !           311: 
        !           312: @example
        !           313: stack        ( "name" "pointer" "type" -- )
        !           314:              ( name execution: -- stack )
        !           315: type-prefix  ( addr u xt1 xt2 n stack "prefix" -- )
        !           316: single       ( -- xt1 xt2 n )
        !           317: double       ( -- xt1 xt2 n )
        !           318: stack-prefix ( stack "prefix" -- )
        !           319: @end example
        !           320: 
        !           321: @section Simple instructions
        !           322: 
        !           323: We will use the following simple VM instruction description as example:
        !           324: 
        !           325: @example
        !           326: sub ( i1 i2 -- i )
        !           327: i = i1-i2;
        !           328: @end example
        !           329: 
        !           330: The first line specifies the name of the VM instruction (@code{sub}) and
        !           331: its stack effect (@code{i1 i2 -- i}).  The rest of the description is
        !           332: just plain C code.
        !           333: 
        !           334: @cindex stack effect
        !           335: The stack effect specifies that @code{sub} pulls two integers from the
        !           336: data stack and puts them in the C variable @code{i1} and @code{i2} (with
        !           337: the rightmost item (@code{i2}) taken from the top of stack) and later
        !           338: pushes one integer (@code{i)) on the data stack (the rightmost item is
        !           339: on the top afterwards).
        !           340: 
        !           341: How do we know the type and stack of the stack items?  Vmgen uses
        !           342: prefixes, similar to Fortran; in contrast to Fortran, you have to
        !           343: define the prefix first:
        !           344: 
        !           345: @example
        !           346: \E s" Cell"   single data-stack type-prefix i
        !           347: @end example
        !           348: 
        !           349: This defines the prefix @code{i} to refer to the type @code{Cell}
        !           350: (defined as @code{long} in @file{mini.h}) and, by default, to the
        !           351: @code{data-stack}.  It also specifies that this type takes one stack
        !           352: item (@code{single}).  The type prefix is part of the variable name.
        !           353: 
        !           354: Before we can use @code{data-stack} in this way, we have to define it:
        !           355: 
        !           356: @example
        !           357: \E stack data-stack sp Cell
        !           358: @end example
        !           359: @c !! use something other than Cell
        !           360: 
        !           361: This line defines the stack @code{data-stack}, which uses the stack
        !           362: pointer @code{sp}, and each item has the basic type @code{Cell}; other
        !           363: types have to fit into one or two @code{Cell}s (depending on whether the
        !           364: type is @code{single} or @code{double} wide), and are converted from and
        !           365: to Cells on accessing the @code{data-stack) with conversion macros
        !           366: (@pxref{Conversion macros}).  Stacks grow towards lower addresses in
        !           367: vmgen.
        !           368: 
        !           369: We can override the default stack of a stack item by using a stack
        !           370: prefix.  E.g., consider the following instruction:
        !           371: 
        !           372: @example
        !           373: lit ( #i -- i )
        !           374: @end example
        !           375: 
        !           376: The VM instruction @code{lit} takes the item @code{i} from the
        !           377: instruction stream (indicated by the prefix @code{#}, and pushes it on
        !           378: the (default) data stack.  The stack prefix is not part of the variable
        !           379: name.  Stack prefixes are defined like this:
        !           380: 
        !           381: @example
        !           382: \E inst-stream stack-prefix #
        !           383: @end example
        !           384: 
        !           385: This definition defines that the stack prefix @code{#} to specifies the
        !           386: ``stack'' @code{inst-stream}.  Since the instruction stream behaves a
        !           387: little differently than an ordinary stack, it is predefined, and you do
        !           388: not need to define it.
        !           389: 
        !           390: The instruction stream contains instructions and their immediate
        !           391: arguments, so specifying that an argument comes from the instruction
        !           392: stream indicates an immediate argument.  Of course, instruction stream
        !           393: arguments can only appear to the left of @code{--} in the stack effect.
        !           394: If there are multiple instruction stream arguments, the leftmost is the
        !           395: first one (just as the intuition suggests).
        !           396: 
        !           397: @section Superinstructions
        !           398: 
        !           399: @section Stacks, types, and prefixes
1.2       anton     400: 
                    401: 
                    402: 
                    403: Invocation
                    404: 
                    405: Input Syntax
                    406: 
                    407: Concepts: Front end, VM, Stacks,  Types, input stream
                    408: 
                    409: Contact

FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>