package erlang

  1. Overview
  2. Docs
type atom =
  1. | Atom of string
and comment =
  1. | Comment of string
and guard = expr list
and name =
  1. | Var_name of string
  2. | Atom_name of atom
  3. | Qualified_name of {
    1. n_mod : name;
    2. n_name : name;
    }
and map_field = {
  1. mf_name : expr;
  2. mf_value : expr;
}
and case = {
  1. c_lhs : pattern list;
  2. c_guard : guard option;
  3. c_rhs : expr;
}
and let_binding = {
  1. lb_lhs : pattern;
  2. lb_rhs : expr;
}
and literal =
  1. | Lit_integer of string
  2. | Lit_char of string
  3. | Lit_binary of string
  4. | Lit_string of string
  5. | Lit_float of string
  6. | Lit_atom of atom
and recv = {
  1. rcv_cases : case list;
  2. rcv_after : case option;
}
and catch_class =
  1. | Class_error
  2. | Class_throw
and try_catch = {
  1. try_expr : expr;
  2. try_catch : case list option;
  3. try_after : expr option;
}
and expr =
  1. | Expr_apply of fun_apply
  2. | Expr_case of expr * case list
  3. | Expr_catch of expr
  4. | Expr_comment of comment * expr
  5. | Expr_cons of expr list * expr
  6. | Expr_fun of case list
  7. | Expr_fun_ref of {
    1. fref_name : name;
    2. fref_arity : int;
    }
  8. | Expr_if of (expr list list * expr) list
  9. | Expr_let of let_binding * expr
  10. | Expr_list of expr list
  11. | Expr_literal of literal
  12. | Expr_macro of string
  13. | Expr_map of map_field list
  14. | Expr_map_update of expr * map_field list
  15. | Expr_name of name
  16. | Expr_nil
  17. | Expr_recv of recv
  18. | Expr_try of try_catch
  19. | Expr_tuple of expr list
and pattern =
  1. | Pattern_binding of name
  2. | Pattern_catch of name option * pattern * name option
  3. | Pattern_cons of pattern list * pattern
  4. | Pattern_ignore
  5. | Pattern_list of pattern list
  6. | Pattern_map of (pattern * pattern) list
  7. | Pattern_match of literal
  8. | Pattern_tuple of pattern list
  9. | Pattern_with_name of pattern * pattern
and fun_apply = {
  1. fa_name : expr;
  2. fa_args : expr list;
}
and fun_decl = {
  1. fd_name : atom;
  2. fd_arity : int;
  3. fd_cases : case list;
  4. fd_spec : type_expr option;
}
and record_field = {
  1. rf_name : atom;
  2. rf_type : type_expr;
}
and type_constr = {
  1. tc_name : name;
  2. tc_args : type_expr list;
}
and field_presence =
  1. | Optional
  2. | Mandatory
and type_map_field = {
  1. tmf_name : type_expr;
  2. tmf_presence : field_presence;
  3. tmf_value : type_expr;
}
and type_expr =
  1. | Type_function of {
    1. tyfun_args : type_expr list;
    2. tyfun_return : type_expr;
    }
  2. | Type_constr of type_constr
  3. | Type_variable of name
  4. | Type_tuple of type_expr list
  5. | Type_list of type_expr
  6. | Type_record of name * record_field list
  7. | Type_map of type_map_field list
  8. | Type_variant of type_expr list
  9. | Type_const of literal
and type_kind =
  1. | Opaque
  2. | Type
  3. | Spec
  4. | Callback
and type_decl = {
  1. typ_expr : type_expr;
  2. typ_kind : type_kind;
  3. typ_name : atom;
  4. typ_params : type_expr list;
}
and export_type =
  1. | Export_function
  2. | Export_type

An exported symbol in an Erlang module. This could be a function or a type. See: http://erlang.org/doc/reference_manual/modules.html for missing fields. http://erlang.org/doc/reference_manual/typespec.html

and export = {
  1. exp_type : export_type;
  2. exp_name : atom;
  3. exp_arity : int;
}
and attribute = {
  1. atr_name : atom;
  2. atr_value : expr;
}
and module_item =
  1. | Module_comment of comment
  2. | Module_attribute of attribute
  3. | Type_decl of type_decl
  4. | Function_decl of fun_decl
and structure = module_item list
and t = {
  1. file_name : string;
  2. behaviours : atom list;
  3. module_name : atom;
  4. attributes : attribute list;
  5. exports : export list;
  6. types : type_decl list;
  7. functions : fun_decl list;
}
val sexp_of_t : t -> Sexplib.Sexp.t
val sexp_of_structure : structure -> Sexplib.Sexp.t
val sexp_of_expr : expr -> Sexplib.Sexp.t