查看源码 erl_eval (stdlib v6.2)

Erlang 元解释器。

此模块为 Erlang 表达式提供了解释器。表达式采用由 erl_parse(Erlang 解析器)或 io 返回的抽象语法形式。

本地函数处理程序

在计算函数时,不能调用本地函数。会生成未定义函数错误。但是,可选参数 LocalFunctionHandler 可以用于定义在调用本地函数时调用的函数。此参数可以具有以下格式:

  • {value,Func} - 这定义了一个本地函数处理程序,使用以下参数调用:

    Func(Name, Arguments)

    Name 是本地函数的名称(一个原子),Arguments 是*已求值*的参数列表。函数处理程序返回本地函数的值。在这种情况下,无法访问当前绑定。要发出错误信号,函数处理程序会使用合适的退出值调用 exit/1

  • {eval,Func} - 这定义了一个本地函数处理程序,使用以下参数调用:

    Func(Name, Arguments, Bindings)

    Name 是本地函数的名称(一个原子),Arguments 是*未求值*的参数列表,Bindings 是当前变量绑定。函数处理程序返回:

    {value,Value,NewBindings}

    Value 是本地函数的值,NewBindings 是更新后的变量绑定。在这种情况下,函数处理程序本身必须计算所有函数参数并管理绑定。要发出错误信号,函数处理程序会使用合适的退出值调用 exit/1

  • none - 没有本地函数处理程序。

非本地函数处理程序

可选参数 NonLocalFunctionHandler 可用于定义在以下情况下调用的函数:

  • 调用函数对象(fun)。
  • 调用内置函数。
  • 使用 M:F 语法调用函数,其中 MF 是原子或表达式。
  • 调用运算符 Op/A(这被视为调用函数 erlang:Op/A)。

异常是对 erlang:apply/2,3 的调用;对于此类调用,不会调用任何函数处理程序。此参数可以具有以下格式:

  • {value,Func} - 这定义了一个非本地函数处理程序。该函数可以使用两个参数调用:

    Func(FuncSpec, Arguments)

    或者三个参数:

    Func(Anno, FuncSpec, Arguments)

    Anno 是节点的 erl_anno:anno()FuncSpec 是函数名称,形式为 {Module,Function} 或 fun,Arguments 是*已求值*的参数列表。函数处理程序返回函数的值。要发出错误信号,函数处理程序会使用合适的退出值调用 exit/1

  • none - 没有非本地函数处理程序。

注意

对于诸如 erlang:apply(Fun, Args)erlang:apply(Module, Function, Args) 之类的调用,对应于对 erlang:apply/2,3 本身的调用的非本地函数处理程序调用(Func({erlang, apply}, [Fun, Args])Func({erlang, apply}, [Module, Function, Args]))永远不会发生。

然而,非本地函数处理程序使用对 erlang:apply/2,3 的调用已求值的参数调用:Func(Fun, Args)Func({Module, Function}, Args)(假设 {Module, Function} 不是 {erlang, apply})。

通过计算 fun 表达式 "fun ... end" 定义的函数的调用也会对非本地函数处理程序隐藏。

非本地函数处理程序参数可能不如本地函数处理程序参数那样频繁使用。一个可能的用途是在调用由于某些原因不允许调用的函数时调用 exit/1

总结

类型

绑定结构。它是一个 map 或一个 orddicterl_eval 将始终返回给定的类型。

在本模块的 本地函数处理程序部分中进一步描述

在本模块的 非本地函数处理程序部分中进一步描述。

函数

将绑定 Name=Value 添加到 BindingStruct。返回更新的绑定结构。

返回 NameBindingStruct 中的绑定。

返回绑定结构中包含的绑定列表。

删除 NameBindingStruct 中的绑定。返回更新的绑定结构。

使用一组绑定 Bindings 计算 ExpressionExpression 是抽象语法中的表达式。

并行计算表达式列表,对每个表达式使用相同的初始绑定。尝试合并从每次计算返回的绑定。

使用一组绑定 Bindings 计算 Expressions,其中 Expressions 是一个表达式序列(抽象语法),其类型可由 io:parse_erl_exprs/2 返回。

返回一个空的绑定结构。

类型

-type binding_struct() :: orddict:orddict() | map().

绑定结构。它是一个 map 或一个 orddicterl_eval 将始终返回给定的类型。

链接到此类型

bindings()

查看源码 (未导出)
-type bindings() :: [{name(), value()}].
链接到此类型

expression()

查看源码 (未导出)
-type expression() :: erl_parse:abstract_expr().
链接到此类型

expression_list()

查看源码 (未导出)
-type expression_list() :: [expression()].
链接到此类型

expressions()

查看源码 (未导出)
-type expressions() :: [erl_parse:abstract_expr()].

erl_parse:parse_exprs/1io:parse_erl_exprs/2 返回。

链接到此类型

func_spec()

查看源码 (未导出)
-type func_spec() :: {Module :: module(), Function :: atom()} | function().
链接到此类型

lfun_eval_handler()

查看源码 (未导出)
-type lfun_eval_handler() ::
          fun((Name :: atom(), Arguments :: expression_list(), Bindings :: binding_struct()) ->
                  {value, Value :: value(), NewBindings :: binding_struct()}).
链接到此类型

lfun_value_handler()

查看源码 (未导出)
-type lfun_value_handler() :: fun((Name :: atom(), Arguments :: [term()]) -> Value :: value()).
链接到此类型

local_function_handler()

查看源码 (未导出)
-type local_function_handler() :: {value, lfun_value_handler()} | {eval, lfun_eval_handler()} | none.

在本模块的 本地函数处理程序部分中进一步描述

链接到此类型

name()

查看源码 (未导出)
-type name() :: term().
链接到此类型

nlfun_handler()

查看源码 (未导出)
-type nlfun_handler() ::
          fun((FuncSpec :: func_spec(), Arguments :: [term()]) -> term()) |
          fun((Anno :: erl_anno:anno(), FuncSpec :: func_spec(), Arguments :: [term()]) -> term()).
链接到此类型

non_local_function_handler()

查看源码 (未导出)
-type non_local_function_handler() :: {value, nlfun_handler()} | none.

在本模块的 非本地函数处理程序部分中进一步描述。

-type value() :: term().

函数

链接到此函数

add_binding(Name, Value, BindingStruct)

查看源码
-spec add_binding(Name, Value, BindingStruct) -> binding_struct()
                     when Name :: name(), Value :: value(), BindingStruct :: binding_struct().

将绑定 Name=Value 添加到 BindingStruct。返回更新的绑定结构。

链接到此函数

binding(Name, BindingStruct)

查看源码
-spec binding(Name, BindingStruct) -> {value, value()} | unbound
                 when Name :: name(), BindingStruct :: binding_struct().

返回 NameBindingStruct 中的绑定。

链接到此函数

bindings(BindingStruct)

查看源码
-spec bindings(BindingStruct :: binding_struct()) -> bindings().

返回绑定结构中包含的绑定列表。

链接到此函数

del_binding(Name, BindingStruct)

查看源码
-spec del_binding(Name, BindingStruct) -> binding_struct()
                     when Name :: name(), BindingStruct :: binding_struct().

删除 NameBindingStruct 中的绑定。返回更新的绑定结构。

链接到此函数

expr(Expression, Bindings)

查看源码
-spec expr(Expression, Bindings) -> {value, Value, NewBindings}
              when
                  Expression :: expression(),
                  Bindings :: binding_struct(),
                  Value :: value(),
                  NewBindings :: binding_struct().

等效于 expr(Expression, Bindings, none)

链接到此函数

expr(Expression, Bindings, LocalFunctionHandler)

查看源码
-spec expr(Expression, Bindings, LocalFunctionHandler) -> {value, Value, NewBindings}
              when
                  Expression :: expression(),
                  Bindings :: binding_struct(),
                  LocalFunctionHandler :: local_function_handler(),
                  Value :: value(),
                  NewBindings :: binding_struct().

等效于 expr(Expression, Bindings, LocalFunctionHandler, none)

链接到此函数

expr(Expression, Bindings, LocalFunctionHandler, NonLocalFunctionHandler)

查看源码
-spec expr(Expression, Bindings, LocalFunctionHandler, NonLocalFunctionHandler) ->
              {value, Value, NewBindings}
              when
                  Expression :: expression(),
                  Bindings :: binding_struct(),
                  LocalFunctionHandler :: local_function_handler(),
                  NonLocalFunctionHandler :: non_local_function_handler(),
                  Value :: value(),
                  NewBindings :: binding_struct().

等效于 expr(Expression, Bindings, LocalFunctionHandler, NonLocalFunctionHandler, none)

链接到此函数

expr(Expression, Bindings, LocalFunctionHandler, NonLocalFunctionHandler, ReturnFormat)

查看源码
-spec expr(Expression, Bindings, LocalFunctionHandler, NonLocalFunctionHandler, ReturnFormat) ->
              {value, Value, NewBindings} | Value
              when
                  Expression :: expression(),
                  Bindings :: binding_struct(),
                  LocalFunctionHandler :: local_function_handler(),
                  NonLocalFunctionHandler :: non_local_function_handler(),
                  ReturnFormat :: none | value,
                  Value :: value(),
                  NewBindings :: binding_struct().

使用一组绑定 Bindings 计算 ExpressionExpression 是抽象语法中的表达式。

有关何时以及如何使用参数 LocalFunctionHandlerNonLocalFunctionHandler 的说明,请参阅本模块中的本地函数处理器非本地函数处理器 部分。

默认情况下返回 {value, Value, NewBindings}。 如果 ReturnFormatvalue,则仅返回 Value

链接到此函数

expr_list(ExpressionList, Bindings)

查看源码
-spec expr_list(ExpressionList, Bindings) -> {ValueList, NewBindings}
                   when
                       ExpressionList :: expression_list(),
                       Bindings :: binding_struct(),
                       ValueList :: [value()],
                       NewBindings :: binding_struct().

等效于 expr_list(ExpressionList, Bindings, none)

链接到此函数

expr_list(ExpressionList, Bindings, LocalFunctionHandler)

查看源码
-spec expr_list(ExpressionList, Bindings, LocalFunctionHandler) -> {ValueList, NewBindings}
                   when
                       ExpressionList :: expression_list(),
                       Bindings :: binding_struct(),
                       LocalFunctionHandler :: local_function_handler(),
                       ValueList :: [value()],
                       NewBindings :: binding_struct().

等效于 expr_list(ExpressionList, Bindings, LocalFunctionHandler, none)

链接到此函数

expr_list(ExpressionList, Bindings, LocalFunctionHandler, NonLocalFunctionHandler)

查看源码
-spec expr_list(ExpressionList, Bindings, LocalFunctionHandler, NonLocalFunctionHandler) ->
                   {ValueList, NewBindings}
                   when
                       ExpressionList :: expression_list(),
                       Bindings :: binding_struct(),
                       LocalFunctionHandler :: local_function_handler(),
                       NonLocalFunctionHandler :: non_local_function_handler(),
                       ValueList :: [value()],
                       NewBindings :: binding_struct().

并行计算表达式列表,对每个表达式使用相同的初始绑定。尝试合并从每次计算返回的绑定。

此函数在 LocalFunctionHandler 中很有用,请参阅本模块中的本地函数处理器部分。

返回 {ValueList, NewBindings}

链接到此函数

exprs(Expressions, Bindings)

查看源码
-spec exprs(Expressions, Bindings) -> {value, Value, NewBindings}
               when
                   Expressions :: expressions(),
                   Bindings :: binding_struct(),
                   Value :: value(),
                   NewBindings :: binding_struct().

等效于 exprs(Expressions, Bindings, none)

链接到此函数

exprs(Expressions, Bindings, LocalFunctionHandler)

查看源码
-spec exprs(Expressions, Bindings, LocalFunctionHandler) -> {value, Value, NewBindings}
               when
                   Expressions :: expressions(),
                   Bindings :: binding_struct(),
                   LocalFunctionHandler :: local_function_handler(),
                   Value :: value(),
                   NewBindings :: binding_struct().

等效于 exprs(Expressions, Bindings, LocalFunctionHandler, none)

链接到此函数

exprs(Expressions, Bindings, LocalFunctionHandler, NonLocalFunctionHandler)

查看源码
-spec exprs(Expressions, Bindings, LocalFunctionHandler, NonLocalFunctionHandler) ->
               {value, Value, NewBindings}
               when
                   Expressions :: expressions(),
                   Bindings :: binding_struct(),
                   LocalFunctionHandler :: local_function_handler(),
                   NonLocalFunctionHandler :: non_local_function_handler(),
                   Value :: value(),
                   NewBindings :: binding_struct().

使用一组绑定 Bindings 计算 Expressions,其中 Expressions 是一个表达式序列(抽象语法),其类型可由 io:parse_erl_exprs/2 返回。

有关何时以及如何使用参数 LocalFunctionHandlerNonLocalFunctionHandler 的说明,请参阅本模块中的本地函数处理器非本地函数处理器 部分。

返回 {value, Value, NewBindings}

-spec new_bindings() -> binding_struct().

返回一个空的绑定结构。