aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/erl_pp.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src/erl_pp.erl')
-rw-r--r--lib/stdlib/src/erl_pp.erl65
1 files changed, 65 insertions, 0 deletions
diff --git a/lib/stdlib/src/erl_pp.erl b/lib/stdlib/src/erl_pp.erl
index 66c80a45cb..7dc19f2e9b 100644
--- a/lib/stdlib/src/erl_pp.erl
+++ b/lib/stdlib/src/erl_pp.erl
@@ -31,25 +31,53 @@
-define(MAXLINE, 72).
+-type(hook_function() :: none
+ | fun((Expr :: erl_parse:abstract_expr(),
+ CurrentIndentation :: integer(),
+ CurrentPrecedence :: non_neg_integer(),
+ HookFunction :: hook_function()) ->
+ io_lib:chars())).
+
%%%
%%% Exported functions
%%%
+-spec(form(Form) -> io_lib:chars() when
+ Form :: erl_parse:abstract_form()).
+
form(Thing) ->
form(Thing, none).
+-spec(form(Form, HookFunction) -> io_lib:chars() when
+ Form :: erl_parse:abstract_form(),
+ HookFunction :: hook_function()).
+
form(Thing, Hook) ->
frmt(lform(Thing, Hook)).
+-spec(attribute(Attribute) -> io_lib:chars() when
+ Attribute :: erl_parse:abstract_form()).
+
attribute(Thing) ->
attribute(Thing, none).
+-spec(attribute(Attribute, HookFunction) -> io_lib:chars() when
+ Attribute :: erl_parse:abstract_form(),
+ HookFunction :: hook_function()).
+
attribute(Thing, Hook) ->
frmt(lattribute(Thing, Hook)).
+-spec(function(Function) -> io_lib:chars() when
+ Function :: erl_parse:abstract_form()).
+
function(F) ->
function(F, none).
+-spec(function(Function, HookFunction) -> io_lib:chars() when
+ Function :: erl_parse:abstract_form(),
+ HookFunction :: hook_function()).
+
function(F, Hook) ->
frmt(lfunction(F, Hook)).
@@ -59,30 +87,67 @@ rule(R) ->
rule(R, Hook) ->
frmt(lrule(R, Hook)).
+-spec(guard(Guard) -> io_lib:chars() when
+ Guard :: [erl_parse:abstract_expr()]).
+
guard(Gs) ->
guard(Gs, none).
+-spec(guard(Guard, HookFunction) -> io_lib:chars() when
+ Guard :: [erl_parse:abstract_expr()],
+ HookFunction :: hook_function()).
+
guard(Gs, Hook) ->
frmt(lguard(Gs, Hook)).
+-spec(exprs(Expressions) -> io_lib:chars() when
+ Expressions :: [erl_parse:abstract_expr()]).
+
exprs(Es) ->
exprs(Es, 0, none).
+-spec(exprs(Expressions, HookFunction) -> io_lib:chars() when
+ Expressions :: [erl_parse:abstract_expr()],
+ HookFunction :: hook_function()).
+
exprs(Es, Hook) ->
exprs(Es, 0, Hook).
+-spec(exprs(Expressions, Indent, HookFunction) -> io_lib:chars() when
+ Expressions :: [erl_parse:abstract_expr()],
+ Indent :: integer(),
+ HookFunction :: hook_function()).
+
exprs(Es, I, Hook) ->
frmt({seq,[],[],[$,],lexprs(Es, Hook)}, I).
+-spec(expr(Expression) -> io_lib:chars() when
+ Expression :: erl_parse:abstract_expr()).
+
expr(E) ->
frmt(lexpr(E, 0, none)).
+-spec(expr(Expression, HookFunction) -> io_lib:chars() when
+ Expression :: erl_parse:abstract_expr(),
+ HookFunction :: hook_function()).
+
expr(E, Hook) ->
frmt(lexpr(E, 0, Hook)).
+-spec(expr(Expression, Indent, HookFunction) -> io_lib:chars() when
+ Expression :: erl_parse:abstract_expr(),
+ Indent :: integer(),
+ HookFunction :: hook_function()).
+
expr(E, I, Hook) ->
frmt(lexpr(E, 0, Hook), I).
+-spec(expr(Expression, Indent, Precedence, HookFunction) -> io_lib:chars() when
+ Expression :: erl_parse:abstract_expr(),
+ Indent :: integer(),
+ Precedence :: non_neg_integer(),
+ HookFunction :: hook_function()).
+
expr(E, I, P, Hook) ->
frmt(lexpr(E, P, Hook), I).