erl_eval
The Erlang Meta Interpreter
This module provides an interpreter for Erlang expressions. The
      expressions are in the abstract syntax as returned by
      erl_parse,
      the Erlang parser, or 
      io.
Types
binding_struct() = orddict:orddict()
A binding structure.
expression() = erl_parse:abstract_expr()
expressions() = [erl_parse:abstract_expr()]
As returned by 
        erl_parse:parse_exprs/1 or
        
        io:parse_erl_exprs/2.
expression_list() = [expression()]
func_spec() = {Module :: module(), Function :: atom()}
                    | function()
    lfun_eval_handler() = 
            fun((Name :: atom(),
                 Arguments :: expression_list(),
                 Bindings :: binding_struct()) ->
                    {value,
                     Value :: value(),
                     NewBindings :: binding_struct()})
    lfun_value_handler() = 
            fun((Name :: atom(), Arguments :: [term()]) ->
                    Value :: value())
    local_function_handler() = {value, lfun_value_handler()}
                                 | {eval, lfun_eval_handler()}
                                 | none
      Further described below.
name() = term()
nlfun_handler() = 
            fun((FuncSpec :: func_spec(), Arguments :: [term()]) -> term())
    non_local_function_handler() = {value, nlfun_handler()} | none
Further described below.
value() = term()
Functions
exprs(Expressions, Bindings) -> {value, Value, NewBindings}
Expressions = expressions()Bindings = binding_struct()Value = value()NewBindings = binding_struct()
exprs(Expressions, Bindings, LocalFunctionHandler) ->
         {value, Value, NewBindings}
    Expressions = expressions()Bindings = binding_struct()LocalFunctionHandler = local_function_handler()Value = value()NewBindings = binding_struct()
exprs(Expressions,
      Bindings,
      LocalFunctionHandler,
      NonLocalFunctionHandler) ->
         {value, Value, NewBindings}
    Expressions = expressions()Bindings = binding_struct()LocalFunctionHandler = local_function_handler()NonLocalFunctionHandler = non_local_function_handler()Value = value()NewBindings = binding_struct()
Evaluates  with the set of bindings
          , where 
          is a sequence of
          expressions (in abstract syntax) of a type which may be
          returned by 
        io:parse_erl_exprs/2. See below for an
          explanation of how and when to use the arguments
           and
          .
          
Returns {value, 
        
expr(Expression, Bindings) -> {value, Value, NewBindings}
Expression = expression()Bindings = binding_struct()Value = value()NewBindings = binding_struct()
expr(Expression, Bindings, LocalFunctionHandler) ->
        {value, Value, NewBindings}
    Expression = expression()Bindings = binding_struct()LocalFunctionHandler = local_function_handler()Value = value()NewBindings = binding_struct()
expr(Expression,
     Bindings,
     LocalFunctionHandler,
     NonLocalFunctionHandler) ->
        {value, Value, NewBindings}
    Expression = expression()Bindings = binding_struct()LocalFunctionHandler = local_function_handler()NonLocalFunctionHandler = non_local_function_handler()Value = value()NewBindings = binding_struct()
expr(Expression,
     Bindings,
     LocalFunctionHandler,
     NonLocalFunctionHandler,
     ReturnFormat) ->
        {value, Value, NewBindings} | Value
    Expression = expression()Bindings = binding_struct()LocalFunctionHandler = local_function_handler()NonLocalFunctionHandler = non_local_function_handler()ReturnFormat = none | valueValue = value()NewBindings = binding_struct()
Evaluates  with the set of bindings
          . 
          is an expression in
          abstract syntax. See below for an explanation of
          how and when to use the arguments
           and
          .
          
Returns {value,  by default. But if the
         is value only
        the  is returned.
expr_list(ExpressionList, Bindings) -> {ValueList, NewBindings}
ExpressionList = expression_list()Bindings = binding_struct()ValueList = [value()]NewBindings = binding_struct()
expr_list(ExpressionList, Bindings, LocalFunctionHandler) ->
             {ValueList, NewBindings}
    ExpressionList = expression_list()Bindings = binding_struct()LocalFunctionHandler = local_function_handler()ValueList = [value()]NewBindings = binding_struct()
expr_list(ExpressionList,
          Bindings,
          LocalFunctionHandler,
          NonLocalFunctionHandler) ->
             {ValueList, NewBindings}
    ExpressionList = expression_list()Bindings = binding_struct()LocalFunctionHandler = local_function_handler()NonLocalFunctionHandler = non_local_function_handler()ValueList = [value()]NewBindings = binding_struct()
Evaluates a list of expressions in parallel, using the same
          initial bindings for each expression. Attempts are made to
          merge the bindings returned from each evaluation.  This
          function is useful in the LocalFunctionHandler. See below.
          
Returns {.
        
new_bindings() -> binding_struct()
Returns an empty binding structure.
bindings(BindingStruct :: binding_struct()) -> bindings()
Returns the list of bindings contained in the binding structure.
binding(Name, BindingStruct) -> {value, value()} | unbound
Name = name()BindingStruct = binding_struct()
Returns the binding of 
          in .
add_binding(Name, Value, BindingStruct) -> binding_struct()
Name = name()Value = value()BindingStruct = binding_struct()
Adds the binding 
          to .
          Returns an updated binding structure.
del_binding(Name, BindingStruct) -> binding_struct()
Name = name()BindingStruct = binding_struct()
Removes the binding of 
          in .
          Returns an updated binding structure.
Local Function Handler
 
      During evaluation of a function, no calls can be made to local
      functions. An undefined function error would be
      generated. However, the optional argument
      LocalFunctionHandler may be used to define a function
      which is called when there is a call to a local function. The
      argument can have the following formats:
{value,Func}This defines a local function handler which is called with:
Func(Name, Arguments)
Name is the name of the local function (an atom) and
          Arguments is a list of the evaluated
          arguments. The function handler returns the value of the
          local function. In this case, it is not possible to access
          the current bindings. To signal an error, the function
          handler just calls exit/1 with a suitable exit value.
{eval,Func}This defines a local function handler which is called with:
Func(Name, Arguments, Bindings)
Name is the name of the local function (an atom),
          Arguments is a list of the unevaluated
          arguments, and Bindings are the current variable
          bindings. The function handler returns:
{value,Value,NewBindings}        
        Value is the value of the local function and
          NewBindings are the updated variable bindings. In
          this case, the function handler must itself evaluate all the
          function arguments and manage the bindings. To signal an
          error, the function handler just calls exit/1 with a
          suitable exit value.
noneThere is no local function handler.
Non-local Function Handler
 
      The optional argument NonlocalFunctionHandler may be
      used to define a function which is called in the following
      cases: a functional object (fun) is called; a built-in function
      is called; a function is called using the M:F syntax, where M
      and F are atoms or expressions; an operator Op/A is called
      (this is handled as a call to the function erlang:Op/A).
      Exceptions are calls to erlang:apply/2,3; neither of the
      function handlers will be called for such calls. 
      The argument can have the following formats:
{value,Func}This defines an nonlocal function handler which is called with:
Func(FuncSpec, Arguments)
FuncSpec is the name of the function on the form
          {Module,Function} or a fun, and Arguments is a
          list of the evaluated arguments. The function
          handler returns the value of the function. To
          signal an error, the function handler just calls
          exit/1 with a suitable exit value.
noneThere is no nonlocal function handler.
Note!
For calls such as erlang:apply(Fun, Args) or
        erlang:apply(Module, Function, Args) the call of the
        non-local function handler corresponding to the call to
        erlang:apply/2,3 itself--Func({erlang, apply}, [Fun, Args]) or Func({erlang, apply}, [Module, Function, Args])--will never take place. The non-local function
        handler will however be called with the evaluated
        arguments of the call to erlang:apply/2,3: Func(Fun, Args) or Func({Module, Function}, Args) (assuming
        that {Module, Function} is not {erlang, apply}).
Calls to functions defined by evaluating fun expressions
        "fun ... end" are also hidden from non-local function
        handlers.
The nonlocal function handler argument is probably not used as
      frequently as the local function handler argument. A possible
      use is to call exit/1 on calls to functions that for some
      reason are not allowed to be called.
Bugs
Undocumented functions in erl_eval should not be used.